]> matita.cs.unibo.it Git - helm.git/blob - helm/searchEngine/searchEngine.ml
35270fd62c8ee31d46ca2469a819b94e57ebfeb8
[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 open Http_types ;;
27
28 let debug = true;;
29 let debug_print s = if debug then prerr_endline s;;
30 Http_common.debug := true;;
31 (* Http_common.debug := true;; *)
32
33   (** accepted HTTP servers for ask_uwobo method forwarding *)
34 let valid_servers = [ "mowgli.cs.unibo.it:58080" ; "mowgli.cs.unibo.it" ; "localhost:58080" ] ;;
35
36 open Printf;;
37
38 let postgresConnectionString =
39  try
40   Sys.getenv "POSTGRESQL_CONNECTION_STRING"
41  with
42   Not_found -> "host=mowgli.cs.unibo.it dbname=helm_mowgli_new_schema user=helm"
43 ;;
44
45 let daemon_name = "Search Engine";;
46 let default_port = 58085;;
47 let port_env_var = "SEARCH_ENGINE_PORT";;
48
49 let pages_dir =
50   try
51     Sys.getenv "SEARCH_ENGINE_HTML_DIR"
52   with Not_found -> "html"  (* relative to searchEngine's document root *)
53 ;;
54 let interactive_user_uri_choice_TPL = pages_dir ^ "/templateambigpdq1.html";;
55 let interactive_interpretation_choice_TPL = pages_dir ^ "/templateambigpdq2.html";;
56 let final_results_TPL = pages_dir ^ "/templateambigpdq3.html";;
57
58 exception Chat_unfinished
59
60   (** pretty print a MathQL query result to an HELM theory file *)
61 let theory_of_result result =
62  let results_no = List.length result in
63   if results_no > 0 then
64    let mode = if results_no > 10 then "linkonly" else "typeonly" in
65    let results =
66     let idx = ref (results_no + 1) in
67      List.fold_right
68       (fun (uri,attrs) i ->
69         decr idx ;
70         "<tr><td valign=\"top\">" ^ string_of_int !idx ^ ".</td><td><ht:OBJECT uri=\"" ^ uri ^ "\" mode=\"" ^ mode ^ "\"/></td></tr>" ^  i
71       ) result ""
72    in
73     "<h1>Query Results:</h1><table xmlns:ht=\"http://www.cs.unibo.it/helm/namespaces/helm-theory\">" ^ results ^ "</table>"
74   else
75     "<h1>Query Results:</h1><p>No results found!</p>"
76 ;;
77
78 let pp_result result =
79  "<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>"
80 ;;
81
82   (** chain application of Pcre substitutions *)
83 let rec apply_substs substs line =
84   match substs with
85   | [] -> line
86   | (rex, templ) :: rest -> apply_substs rest (Pcre.replace ~rex ~templ line)
87   (** fold like function on files *)
88 let fold_file f init fname =
89   let inchan = open_in fname in
90   let rec fold_lines' value =
91     try 
92       let line = input_line inchan in 
93       fold_lines' (f value line)
94     with End_of_file -> value
95   in
96   let res = (try fold_lines' init with e -> (close_in inchan; raise e)) in
97   close_in inchan;
98   res
99   (** iter like function on files *)
100 let iter_file f = fold_file (fun _ line -> f line) ()
101
102 let (title_tag_RE, choices_tag_RE, msg_tag_RE, id_to_uris_RE, id_RE,
103     interpretations_RE, interpretations_labels_RE, results_RE, new_aliases_RE)
104   =
105   (Pcre.regexp "@TITLE@", Pcre.regexp "@CHOICES@", Pcre.regexp "@MSG@",
106   Pcre.regexp "@ID_TO_URIS@", Pcre.regexp "@ID@",
107   Pcre.regexp "@INTERPRETATIONS@", Pcre.regexp "@INTERPRETATIONS_LABELS@",
108   Pcre.regexp "@RESULTS@", Pcre.regexp "@NEW_ALIASES@")
109 let server_and_port_url_RE = Pcre.regexp "^http://([^/]+)/.*$"
110
111 exception NotAnInductiveDefinition
112
113 let port =
114   try
115     int_of_string (Sys.getenv port_env_var)
116   with
117   | Not_found -> default_port
118   | Failure "int_of_string" ->
119       prerr_endline "Warning: invalid port, reverting to default";
120       default_port
121 in
122 let pp_error = sprintf "<html><body><h1>Error: %s</h1></body></html>" in
123 let bad_request body outchan =
124   Http_daemon.respond_error ~status:(`Client_error `Bad_request) ~body outchan
125 in
126 let contype = "Content-Type", "text/html" in
127
128 (* SEARCH ENGINE functions *)
129
130 let refine_constraints (constr_obj, constr_rel, constr_sort) =
131  function
132     "/searchPattern" ->
133       (constr_obj, constr_rel, constr_sort),
134        (Some constr_obj, Some constr_rel, Some constr_sort)
135   | "/matchConclusion" ->
136       let constr_obj' =
137        List.map
138         (function (uri,pos,_) -> (uri,pos,None))
139         (List.filter
140           (function (uri,pos,depth) as constr ->
141             pos="http://www.cs.unibo.it/helm/schemas/schema-helm#MainConclusion"
142             or
143             pos="http://www.cs.unibo.it/helm/schemas/schema-helm#InConclusion"
144           ) constr_obj)
145       in
146        (*CSC: we must select the must constraints here!!! *)
147        (constr_obj',[],[]),(Some constr_obj', None, None)
148   | _ -> assert false
149 in
150
151 let get_constraints term =
152  function
153     "/locateInductivePrinciple" ->
154       let uri = 
155        match term with
156           Cic.MutInd (uri,t,_) -> MQueryUtil.string_of_uriref (uri,[t])
157         | _ -> raise NotAnInductiveDefinition
158       in
159       let constr_obj =
160        [uri,"http://www.cs.unibo.it/helm/schemas/schema-helm#InHypothesis",
161          None ;
162         uri,"http://www.cs.unibo.it/helm/schemas/schema-helm#MainHypothesis",
163          Some 0
164        ]
165       in
166       let constr_rel =
167        ["http://www.cs.unibo.it/helm/schemas/schema-helm#MainConclusion",
168         None] in
169       let constr_sort =
170        ["http://www.cs.unibo.it/helm/schemas/schema-helm#MainHypothesis",
171         Some 1, "http://www.cs.unibo.it/helm/schemas/schema-helm#Prop"]
172       in
173        (constr_obj, constr_rel, constr_sort), (None,None,None)
174   | req_path ->
175      let must = MQueryLevels2.get_constraints term in
176       refine_constraints must req_path
177 in
178
179 (* HTTP DAEMON CALLBACK *)
180
181 let callback (req: Http_types.request) outchan =
182   try
183     debug_print (sprintf "Received request: %s" req#path);
184     if req#path <> "/getpage" then
185       Mqint.init postgresConnectionString;
186     (match req#path with
187     | "/execute" ->
188         let query_string = req#param "query" in
189         let lexbuf = Lexing.from_string query_string in
190         let query = MQueryUtil.query_of_text lexbuf in
191         let result = MQueryGenerator.execute_query query in
192         let result_string = pp_result result in
193         Http_daemon.respond ~body:result_string ~headers:[contype] outchan
194     | "/locate" ->
195         let id = req#param "id" in
196         let result = MQueryGenerator.locate id in
197         Http_daemon.respond ~headers:[contype] ~body:(pp_result result) outchan
198     | "/getpage" ->
199         (* TODO implement "is_permitted" *)
200         (let is_permitted _ = true in
201         let remove_fragment uri = Pcre.replace ~pat:"#.*" uri in
202         let page = remove_fragment (req#param "url") in
203         let preprocess =
204           (try
205             bool_of_string (req#param "preprocess")
206           with Invalid_argument _ | Http_types.Param_not_found _ -> false)
207         in
208         (match page with
209         | page when is_permitted page ->
210             (let fname = sprintf "%s/%s" pages_dir (remove_fragment page) in
211             Http_daemon.send_basic_headers ~code:200 outchan;
212             Http_daemon.send_header "Content-Type" "text/html" outchan;
213             Http_daemon.send_CRLF outchan;
214             if preprocess then begin
215               iter_file
216                 (fun line ->
217                   output_string outchan
218                     ((apply_substs
219                        (List.map
220                          (function (key,value) ->
221                            let key' =
222                             (Pcre.extract ~pat:"param\\.(.*)" key).(1)
223                            in
224                             Pcre.regexp ("@" ^ key' ^ "@"), value
225                          )
226                          (List.filter
227                            (fun (key,_) as p-> Pcre.pmatch ~pat:"^param\\." key)
228                            req#params)
229                        )
230                        line) ^
231                     "\n"))
232                 fname
233             end else
234               Http_daemon.send_file ~src:(FileSrc fname) outchan)
235         | page -> Http_daemon.respond_forbidden ~url:page outchan))
236     | "/ask_uwobo" ->
237       let url = req#param "url" in
238       let server_and_port =
239         (Pcre.extract ~rex:server_and_port_url_RE url).(1)
240       in
241       if List.mem server_and_port valid_servers then
242         Http_daemon.respond
243           ~headers:["Content-Type", "text/html"]
244           ~body:(Http_client.Convenience.http_get url)
245           outchan
246       else
247         Http_daemon.respond
248           ~body:(pp_error ("Untrusted UWOBO server: " ^ server_and_port))
249           outchan
250     | "/searchPattern"
251     | "/matchConclusion"
252     | "/locateInductivePrinciple" ->
253         let term_string = req#param "term" in
254         let lexbuf = Lexing.from_string term_string in
255         let (context, metasenv) = ([], []) in
256         let (dom, mk_metasenv_and_expr) =
257           CicTextualParserContext.main
258             ~context ~metasenv CicTextualLexer.token lexbuf
259         in
260         let id_to_uris_raw = req#param "aliases" in
261         let tokens = Pcre.split ~pat:"\\s" id_to_uris_raw in
262         let rec parse_tokens keys lookup = function (* TODO spostarla fuori *)
263           | [] -> keys, lookup
264           | "alias" :: key :: value :: rest ->
265               let key' = CicTextualParser0.Id key in
266                parse_tokens
267                  (key'::keys)
268                  (fun id ->
269                    if id = key' then
270                      Some
271                       (CicTextualParser0.Uri (MQueryMisc.cic_textual_parser_uri_of_string value))
272                    else lookup id)
273                  rest
274           | _ -> failwith "Can't parse aliases"
275         in
276         let parse_choices choices_raw =
277           let choices = Pcre.split ~pat:";" choices_raw in
278           List.fold_left
279             (fun f x ->
280               match Pcre.split ~pat:"\\s" x with
281               | ""::id::tail
282               | id::tail when id<>"" ->
283                   (fun id' ->
284 prerr_endline ("#### " ^ id ^ " :=");
285 List.iter (fun u -> prerr_endline ("<" ^ Netencoding.Url.decode u ^ ">")) tail;
286                     if id = id' then
287                       Some (List.map (fun u -> Netencoding.Url.decode u) tail)
288                     else
289                       f id')
290               | _ -> failwith "Can't parse choices")
291             (fun _ -> None)
292             choices
293         in
294         let (id_to_uris : Disambiguate.domain_and_interpretation) =
295          parse_tokens [] (fun _ -> None) tokens in
296         let id_to_choices =
297           try
298             let choices_raw = req#param "choices" in
299             parse_choices choices_raw
300           with Http_types.Param_not_found _ -> (fun _ -> None)
301         in
302         let module Chat: Disambiguate.Callbacks =
303           struct
304
305             let get_metasenv () =
306              !CicTextualParser0.metasenv
307
308             let set_metasenv metasenv =
309               CicTextualParser0.metasenv := metasenv
310
311             let output_html = prerr_endline
312
313             let interactive_user_uri_choice
314               ~selection_mode ?ok
315               ?enable_button_for_non_vars ~(title: string) ~(msg: string)
316               ~(id: string) (choices: string list)
317               =
318                 (match id_to_choices id with
319                 | Some choices -> choices
320                 | None ->
321                   let msg = Pcre.replace ~pat:"\"" ~templ:"\\\"" msg in
322                   (match selection_mode with
323                   | `SINGLE -> assert false
324                   | `EXTENDED ->
325                       Http_daemon.send_basic_headers ~code:200 outchan ;
326                       Http_daemon.send_CRLF outchan ;
327                       iter_file
328                         (fun line ->
329                           let formatted_choices =
330                             String.concat ","
331                               (List.map (fun uri -> sprintf "\"%s\"" uri) choices)
332                           in
333                           let processed_line =
334                             apply_substs
335                               [title_tag_RE, title;
336                                choices_tag_RE, formatted_choices;
337                                msg_tag_RE, msg;
338                                id_to_uris_RE, id_to_uris_raw;
339                                id_RE, id]
340                               line
341                           in
342                           output_string outchan (processed_line ^ "\n"))
343                         interactive_user_uri_choice_TPL;
344                       raise Chat_unfinished))
345
346             let interactive_interpretation_choice interpretations =
347               let html_interpretations_labels =
348                 String.concat ", "
349                   (List.map
350                     (fun l ->
351                       "\"" ^
352                       (String.concat "<br />"
353                         (List.map
354                           (fun (id, value) ->
355                             (sprintf "alias %s %s" id value))
356                           l)) ^
357                       "\"")
358                   interpretations)
359               in
360               let html_interpretations =
361                 String.concat ", "
362                   (List.map
363                     (fun l ->
364                       "\"" ^
365                       (String.concat " "
366                         (List.map
367                           (fun (id, value) ->
368                             (sprintf "alias %s %s"
369                               id
370                               (MQueryMisc.wrong_xpointer_format_from_wrong_xpointer_format'
371                                 value)))
372                           l)) ^
373                       "\"")
374                     interpretations)
375               in
376               Http_daemon.send_basic_headers ~code:200 outchan ;
377               Http_daemon.send_CRLF outchan ;
378               iter_file
379                 (fun line ->
380                   let processed_line =
381                     apply_substs
382                       [interpretations_RE, html_interpretations;
383                        interpretations_labels_RE, html_interpretations_labels]
384                       line
385                   in
386                   output_string outchan (processed_line ^ "\n"))
387                 interactive_interpretation_choice_TPL;
388               raise Chat_unfinished
389
390             let input_or_locate_uri ~title =
391               UriManager.uri_of_string "cic:/Coq/Init/DataTypes/nat_ind.con"
392
393           end
394         in
395         let module Disambiguate' = Disambiguate.Make (Chat) in
396         let (id_to_uris', metasenv', term') =
397           Disambiguate'.disambiguate_input
398             context metasenv dom mk_metasenv_and_expr id_to_uris
399         in
400         (match metasenv' with
401         | [] ->
402             let must',only = get_constraints term' req#path in
403             let results = MQueryGenerator.searchPattern must' only in 
404             Http_daemon.send_basic_headers ~code:200 outchan ;
405             Http_daemon.send_CRLF outchan ;
406             iter_file
407               (fun line ->
408                 let new_aliases =
409                   match id_to_uris' with
410                   | (domain, f) ->
411                       String.concat ", "
412                         (List.map
413                           (fun name ->
414                             sprintf "\"alias %s cic:%s\""
415                               (match name with
416                                   CicTextualParser0.Id name -> name
417                                 | _ -> assert false (*CSC: completare *))
418                               (match f name with
419                               | None -> assert false
420                               | Some (CicTextualParser0.Uri t) ->
421                                   MQueryMisc.string_of_cic_textual_parser_uri
422                                     t
423                               | _ -> assert false (*CSC: completare *)))
424                           domain)
425                 in
426                 let processed_line =
427                   apply_substs
428                     [results_RE, theory_of_result results ;
429                      new_aliases_RE, new_aliases]
430                     line
431                 in
432                 output_string outchan (processed_line ^ "\n"))
433               final_results_TPL
434         | _ -> (* unable to instantiate some implicit variable *)
435             Http_daemon.respond
436               ~headers:[contype]
437               ~body:"some implicit variables are still unistantiated :-("
438               outchan)
439
440     | invalid_request ->
441         Http_daemon.respond_error ~status:(`Client_error `Bad_request) outchan);
442     if req#path <> "/getpage" then
443       Mqint.close ();
444     debug_print (sprintf "%s done!" req#path)
445   with
446   | Chat_unfinished -> prerr_endline "Chat unfinished, Try again!"
447   | Http_types.Param_not_found attr_name ->
448       bad_request (sprintf "Parameter '%s' is missing" attr_name) outchan
449   | exc ->
450       Http_daemon.respond
451         ~body:(pp_error ("Uncaught exception: " ^ (Printexc.to_string exc)))
452         outchan
453 in
454 printf "%s started and listening on port %d\n" daemon_name port;
455 printf "Current directory is %s\n" (Sys.getcwd ());
456 printf "HTML directory is %s\n" pages_dir;
457 flush stdout;
458 Unix.putenv "http_proxy" "";
459 Mqint.set_database Mqint.postgres_db;
460 Http_daemon.start' ~port callback;
461 printf "%s is terminating, bye!\n" daemon_name
462