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