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