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