]> matita.cs.unibo.it Git - helm.git/blob - helm/searchEngine/searchEngine.ml
connected instance to the web search engine
[helm.git] / helm / searchEngine / searchEngine.ml
1 (* Copyright (C) 2002-2005, 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 open Printf
27
28 let debug = true
29 let debug_print s = if debug then prerr_endline s
30 let _ = Http_common.debug := false
31
32 exception Chat_unfinished
33 exception Unbound_identifier of string
34 exception Invalid_action of string  (* invalid action for "/search" method *)
35
36   (** raised by elim when a MutInd is required but not found *)
37 exception Not_a_MutInd
38
39 let daemon_name = "Whelp"
40 let configuration_file = "/projects/helm/etc/whelp.conf.xml"
41
42 let placeholders = [
43   "ACTION"; "ADVANCED"; "ADVANCED_CHECKED"; "CHOICES"; "CURRENT_CHOICES";
44   "EXPRESSION"; "ID"; "IDEN"; "ID_TO_URIS"; "INTERPRETATIONS";
45   "INTERPRETATIONS_LABELS"; "MSG"; "NEW_ALIASES"; "NEXT_LINK"; "NO_CHOICES";
46   "PAGE"; "PAGES"; "PREV_LINK"; "QUERY_KIND"; "QUERY_SUMMARY"; "RESULTS";
47   "SEARCH_ENGINE_URL"; "SIMPLE_CHECKED"; "TITLE";
48 ]
49
50 let tag =
51   let regexps = Hashtbl.create 25 in
52   List.iter
53     (fun tag -> Hashtbl.add regexps tag (Pcre.regexp (sprintf "@%s@" tag)))
54     placeholders;
55   fun name ->
56     try
57       Hashtbl.find regexps name
58     with Not_found -> assert false
59
60   (* First of all we load the configuration *)
61 let _ = Helm_registry.load_from configuration_file
62 let port = Helm_registry.get_int "search_engine.port"
63 let pages_dir = Helm_registry.get "search_engine.html_dir"
64
65 let moogle_TPL = pages_dir ^ "/moogle.html"
66 let choices_TPL = pages_dir ^ "/moogle_chat.html"
67
68 let my_own_url =
69  let ic = Unix.open_process_in "hostname -f" in
70  let hostname = input_line ic in
71  ignore (Unix.close_process_in ic);
72  sprintf "http://%s:%d" hostname port
73 let _ = Helm_registry.set "search_engine.my_own_url" my_own_url
74
75 let bad_request body outchan =
76   Http_daemon.respond_error ~code:(`Status (`Client_error `Bad_request)) ~body
77     outchan
78
79   (** chain application of Pcre substitutions *)
80 let rec apply_substs substs line =
81   match substs with
82   | [] -> line
83   | (rex, templ) :: rest -> apply_substs rest (Pcre.replace ~rex ~templ line)
84   (** fold like function on files *)
85 let fold_file f init fname =
86   let inchan = open_in fname in
87   let rec fold_lines' value =
88     try 
89       let line = input_line inchan in 
90       fold_lines' (f value line)
91     with End_of_file -> value
92   in
93   let res = (try fold_lines' init with e -> (close_in inchan; raise e)) in
94   close_in inchan;
95   res
96   (** iter like function on files *)
97 let iter_file f = fold_file (fun _ line -> f line) ()
98 let javascript_quote s =
99  let rex = Pcre.regexp "'" in
100  let rex' = Pcre.regexp "\"" in
101   Pcre.replace ~rex ~templ:"\\'"
102    (Pcre.replace ~rex:rex' ~templ:"\\\"" s)
103 let string_tail s =
104   let len = String.length s in
105   String.sub s 1 (len-1)
106 let nonvar s =
107   let len = String.length s in
108   let suffix = String.sub s (len-4) 4 in
109   not (suffix  = ".var")
110
111 let add_param_substs params =
112   List.map
113     (fun (key,value) ->
114       let key' = (Pcre.extract ~pat:"param\\.(.*)" key).(1) in
115       Pcre.regexp ("@" ^ key' ^ "@"), value)
116     (List.filter
117       (fun ((key,_) as p) -> Pcre.pmatch ~pat:"^param\\." key)
118       params)
119
120 let page_RE = Pcre.regexp "&param\\.page=\\d+"
121 let identifier_RE = Pcre.regexp "^\\s*\\w+\\s*$"
122
123 let query_kind_of_req (req: Http_types.request) =
124   match req#path with
125   | "/match" -> "Match"
126   | "/hint" -> "Hint"
127   | "/locate" -> "Locate"
128   | "/elim" -> "Elim"
129   | "/instance" -> "Instance"
130   | _ -> ""
131
132   (* given a uri with a query part in input try to find in it a string
133    * "&param_name=..." (where param_name is given). If found its value will be
134    * set to param_value. If not, a trailing "&param_name=param_value" (where
135    * both are given) is added to the input string *)
136 let patch_param param_name param_value url =
137   let rex = Pcre.regexp (sprintf "&%s=[^&]*" (Pcre.quote param_name)) in
138   if Pcre.pmatch ~rex url then
139     Pcre.replace ~rex ~templ:(sprintf "%s=%s" param_name param_value) url
140   else
141     sprintf "%s&%s=%s" url param_name param_value
142
143   (** HTML encoding, e.g.: "<" -> "&lt;" *)
144 let html_encode = Netencoding.Html.encode_from_latin1
145
146 let send_results results
147   ?(id_to_uris = CicTextualParser2.EnvironmentP3.of_string "") 
148    (req: Http_types.request) outchan
149   =
150   let query_kind = query_kind_of_req req in
151   let interp = try req#param "interp" with Http_types.Param_not_found _ -> "" in
152   let page_link anchor page =
153     try
154       let this = req#param "this" in
155       let target =
156         (patch_param "param.interp" interp
157            (patch_param "param.page" (string_of_int page)
158               this))
159       in
160       let target = Pcre.replace ~pat:"&" ~templ:"&amp;" target in
161       sprintf "<a href=\"%s\">%s</a>" target anchor
162     with Http_types.Param_not_found _ -> ""
163   in
164   Http_daemon.send_basic_headers ~code:(`Code 200) outchan ;
165   Http_daemon.send_header "Content-Type" "text/xml" outchan;
166   Http_daemon.send_CRLF outchan ;
167   let subst =
168     match results with
169     | `Results results ->
170         let page = try int_of_string (req#param "page") with _ -> 1 in
171         let results_no = List.length results in
172         let results_per_page =
173           Helm_registry.get_int "search_engine.results_per_page"
174         in
175         let pages =
176           if results_no mod results_per_page = 0 then
177             results_no / results_per_page
178           else
179             results_no / results_per_page + 1
180         in
181         let pages = if pages = 0 then 1 else pages in
182         let (summary, results) = MooglePp.theory_of_result page results in
183         [ tag "PAGE", string_of_int page;
184           tag "PAGES", string_of_int pages;
185           tag "PREV_LINK", (if page > 1 then page_link "Prev" (page-1) else "");
186           tag "NEXT_LINK",
187             (if page < pages then page_link "Next" (page+1) else "");
188           tag "QUERY_KIND", query_kind;
189           tag "QUERY_SUMMARY", summary;
190           tag "RESULTS", results ]
191     | `Error msg ->
192         [ tag "PAGE", "1";
193           tag "PAGES", "1";
194           tag "PREV_LINK", "";
195           tag "NEXT_LINK", "";
196           tag "QUERY_KIND", query_kind;
197           tag "QUERY_SUMMARY", "error";
198           tag "RESULTS", msg ]
199   in
200   let advanced =
201     try
202       req#param "advanced"
203     with Http_types.Param_not_found _ -> "no"
204   in
205   let subst =
206     (tag "SEARCH_ENGINE_URL", my_own_url) ::
207     (tag "ADVANCED", advanced) ::
208     (tag "EXPRESSION", html_encode (req#param "expression")) ::
209     add_param_substs req#params @
210     (if advanced = "no" then
211       [ tag "SIMPLE_CHECKED", "checked='true'";
212         tag "ADVANCED_CHECKED", "" ]
213     else
214       [ tag "SIMPLE_CHECKED", "";
215         tag "ADVANCED_CHECKED", "checked='true'" ]) @
216     subst
217   in
218   iter_file
219     (fun line ->
220       let new_aliases =
221         CicTextualParser2.EnvironmentP3.to_string id_to_uris
222       in
223       let processed_line =
224         apply_substs
225           (* CSC: Bug here: this is a string, not an array! *)
226           ((tag "NEW_ALIASES", "'" ^ javascript_quote new_aliases ^ "'") ::
227             subst) 
228           line
229       in
230       output_string outchan (processed_line ^ "\n"))
231     moogle_TPL
232
233 let exec_action dbd (req: Http_types.request) outchan =
234   let term_str = req#param "expression" in
235   try
236     if req#path = "/elim" && not (Pcre.pmatch ~rex:identifier_RE term_str) then
237       raise Not_a_MutInd;
238     let (context, metasenv) = ([], []) in
239     let id_to_uris_raw = 
240       try req#param "aliases" 
241       with Http_types.Param_not_found _ -> ""
242     in
243     let parse_interpretation_choices choices =
244       List.map int_of_string (Pcre.split ~pat:" " choices) in
245     let parse_choices choices_raw =
246       let choices = Pcre.split ~pat:";" choices_raw in
247       List.fold_left
248         (fun f x ->
249            match Pcre.split ~pat:"\\s" x with
250              | ""::id::tail
251              | id::tail when id<>"" ->
252                  (fun id' ->
253                     if id = id' then
254                       Some (List.map (fun u -> Netencoding.Url.decode u) tail)
255                     else
256                       f id')
257              | _ -> failwith "Can't parse choices")
258         (fun _ -> None)
259         choices
260     in
261     let id_to_uris = CicTextualParser2.EnvironmentP3.of_string id_to_uris_raw in
262     let id_to_choices =
263       try
264         parse_choices (req#param "choices")
265       with Http_types.Param_not_found _ -> (fun _ -> None)
266     in
267     let interpretation_choices =
268       try
269         let choices_raw = req#param "interpretation_choices" in
270         if choices_raw = "" then None 
271         else Some (parse_interpretation_choices choices_raw)
272       with Http_types.Param_not_found _ -> None
273     in 
274     let module Chat: DisambiguateTypes.Callbacks =
275       struct
276         let interactive_user_uri_choice ~selection_mode ?ok
277           ?enable_button_for_non_vars ~(title: string) ~(msg: string)
278           ~(id: string) (choices: string list)
279         =
280           match id_to_choices id with
281           | Some choices -> choices
282           | None -> List.filter nonvar choices
283
284         let interactive_interpretation_choice interpretations =
285           match interpretation_choices with
286           | Some l -> l
287           | None ->
288               let html_interpretations =
289                 MooglePp.html_of_interpretations interpretations
290               in
291               Http_daemon.send_basic_headers ~code:(`Code 200) outchan ;
292               Http_daemon.send_CRLF outchan ;
293               let advanced =
294                 try
295                   req#param "advanced"
296                 with Http_types.Param_not_found _ -> "no"
297               in
298               let query_kind = query_kind_of_req req in
299               iter_file
300                 (fun line ->
301                    let processed_line =
302                      apply_substs
303                        [ tag "SEARCH_ENGINE_URL", my_own_url;
304                          tag "ADVANCED", advanced;
305                          tag "INTERPRETATIONS", html_interpretations;
306                          tag "CURRENT_CHOICES", req#param "choices";
307                          tag "EXPRESSION", html_encode (req#param "expression");
308                          tag "QUERY_KIND", query_kind;
309                          tag "QUERY_SUMMARY", "disambiguation";
310                          tag "ACTION", string_tail req#path ]
311                        line
312                    in
313                    output_string outchan (processed_line ^ "\n"))
314                 choices_TPL;
315               raise Chat_unfinished
316
317         let input_or_locate_uri ~title ?id () =
318           match id with
319           | Some id -> raise (Unbound_identifier id)
320           | None -> assert false
321       end
322     in
323     let module Disambiguate' = Disambiguate.Make(Chat) in
324     let ast = CicTextualParser2.parse_term (Stream.of_string term_str) in
325     let (id_to_uris, metasenv, term) =
326       match
327         Disambiguate'.disambiguate_term ~dbd ~context ~metasenv
328           ~aliases:id_to_uris ast
329       with
330       | [id_to_uris,metasenv,term,_] -> id_to_uris,metasenv,term
331       | _ -> assert false
332     in
333     let uris =
334       match req#path with
335       | "/match" -> MetadataQuery.match_term ~dbd term
336       | "/instance" -> MetadataQuery.instance ~dbd term
337       | "/hint" ->
338           let status = ProofEngineTypes.initial_status term metasenv in
339           let intros = PrimitiveTactics.intros_tac () in
340           let subgoals = ProofEngineTypes.apply_tactic intros status in
341           (match subgoals with
342           | proof, [goal] ->
343               let (uri,metasenv,bo,ty) = proof in
344               List.map fst (MetadataQuery.experimental_hint ~dbd (proof, goal))
345           | _ -> assert false)
346       | "/elim" ->
347           let uri =
348             match term with
349             | Cic.MutInd (uri, typeno, _) ->
350                 UriManager.string_of_uriref (uri, [typeno])
351             | _ -> raise Not_a_MutInd
352           in
353           MetadataQuery.elim ~dbd uri
354       | _ -> assert false
355     in
356     send_results ~id_to_uris (`Results uris) req outchan
357   with
358   | Not_a_MutInd ->
359       send_results (`Error (MooglePp.pp_error "Not an inductive type"
360         ("elim requires as input an identifier corresponding to an inductive"
361          ^ " type")))
362         req outchan
363
364 let callback dbd (req: Http_types.request) outchan =
365   try
366     debug_print (sprintf "Received request: %s" req#path);
367     (match req#path with
368     | "/getpage" ->
369           (* TODO implement "is_permitted" *)
370         (let is_permitted page = not (Pcre.pmatch ~pat:"/" page) in
371         let page = req#param "url" in
372         let fname = sprintf "%s/%s" pages_dir page in
373         let preprocess =
374           (try
375             bool_of_string (req#param "preprocess")
376           with Invalid_argument _ | Http_types.Param_not_found _ -> false)
377         in
378         (match page with
379         | page when is_permitted page && Sys.file_exists fname ->
380             Http_daemon.send_basic_headers ~code:(`Code 200) outchan;
381             Http_daemon.send_header "Content-Type" "text/html" outchan;
382             Http_daemon.send_CRLF outchan;
383             if preprocess then begin
384               iter_file
385                 (fun line ->
386                   output_string outchan
387                     ((apply_substs
388                        ((tag "SEARCH_ENGINE_URL", my_own_url) ::
389                         (tag "ADVANCED", "no") ::
390                         (tag "RESULTS", "") ::
391                         add_param_substs req#params)
392                        line) ^
393                     "\n"))
394                 fname
395             end else
396               Http_daemon.send_file ~src:(Http_types.FileSrc fname) outchan
397         | page -> Http_daemon.respond_forbidden ~url:page outchan))
398     | "/help" -> Http_daemon.respond ~body:daemon_name outchan
399     | "/locate" ->
400         let initial_expression =
401           try req#param "expression" with Http_types.Param_not_found _ -> ""
402         in
403         let expression =
404           Pcre.replace ~pat:"\\s*$"
405             (Pcre.replace ~pat:"^\\s*" initial_expression)
406         in
407         if expression = "" then
408           send_results (`Results []) req outchan
409         else begin
410           let results = MetadataQuery.locate ~dbd expression in
411           send_results (`Results results) req outchan
412         end
413     | "/hint"
414     | "/elim"
415     | "/instance"
416     | "/match" -> exec_action dbd req outchan
417     | invalid_request ->
418         Http_daemon.respond_error ~code:(`Status (`Client_error `Bad_request))
419           outchan);
420     debug_print (sprintf "%s done!" req#path)
421   with
422   | Chat_unfinished -> ()
423   | Http_types.Param_not_found attr_name ->
424       bad_request (sprintf "Parameter '%s' is missing" attr_name) outchan
425   | CicTextualParser2.Parse_error (_, msg) ->
426       send_results (`Error (MooglePp.pp_error "Parse error" msg)) req outchan
427   | Unbound_identifier id ->
428       send_results (`Error (MooglePp.pp_error "Unbound identifier" id)) req
429         outchan
430   | exn ->
431       let exn_string = Printexc.to_string exn in
432       debug_print exn_string;
433       let msg = MooglePp.pp_error "Uncaught exception" exn_string in
434       send_results (`Error msg) req outchan
435
436 let restore_environment () =
437   match
438     Helm_registry.get_opt Helm_registry.get "search_engine.environment_dump"
439   with
440   | None -> ()
441   | Some fname ->
442       printf "Restoring Cic environment from %s ... " fname; flush stdout;
443       let ic = open_in fname in
444       CicEnvironment.restore_from_channel ic;
445       close_in ic;
446       printf "done!\n"; flush stdout
447
448 let _ =
449   printf "%s started and listening on port %d\n" daemon_name port;
450   printf "Current directory is %s\n" (Sys.getcwd ());
451   printf "HTML directory is %s\n" pages_dir;
452   flush stdout;
453   Unix.putenv "http_proxy" "";
454   let dbd =
455     Mysql.quick_connect
456       ~host:(Helm_registry.get "db.host")
457       ~database:(Helm_registry.get "db.database")
458       ~user:(Helm_registry.get "db.user")
459       ()
460   in
461   restore_environment ();
462   Http_daemon.start' ~port (callback dbd);
463   printf "%s is terminating, bye!\n" daemon_name
464