]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/searchEngine/searchEngine.ml
moogle snapshot
[helm.git] / helm / searchEngine / searchEngine.ml
index 35650c8c6cf7e50ab4ee59273bbd60d7496c830a..97e91ebe5d942845d7ce1dc339e91b15983d46ec 100644 (file)
@@ -35,30 +35,46 @@ let debug_print s = if debug then prerr_endline s;;
 Http_common.debug := true;;
 (* Http_common.debug := true;; *)
 
-  (** accepted HTTP servers for ask_uwobo method forwarding *)
-let valid_servers =
- [ "mowgli.cs.unibo.it:58080" ; "mowgli.cs.unibo.it" ; "localhost:58080" ];;
-
-let mqi_flags = [] (* default MathQL interpreter options *)
-
 open Printf;;
 
 let daemon_name = "Search Engine";;
-let default_port = 58085;;
-let port_env_var = "SEARCH_ENGINE_PORT";;
 
-let pages_dir =
-  try
-    Sys.getenv "SEARCH_ENGINE_HTML_DIR"
-  with Not_found -> "html"  (* relative to searchEngine's document root *)
+  (* First of all we load the configuration *)
+let _ =
+ let configuration_file = "searchEngine.conf.xml" in
+  Helm_registry.load_from configuration_file
 ;;
+
+let port = Helm_registry.get_int "search_engine.port";;
+
+let pages_dir = Helm_registry.get "search_engine.html_dir";;
+
+  (** accepted HTTP servers for ask_uwobo method forwarding *)
+let valid_servers= Helm_registry.get_string_list "search_engine.valid_servers";;
+
 let interactive_user_uri_choice_TPL = pages_dir ^ "/templateambigpdq1.html";;
 let interactive_interpretation_choice_TPL =
   pages_dir ^ "/templateambigpdq2.html";;
 let constraints_choice_TPL = pages_dir ^ "/constraints_choice_template.html";;
-let final_results_TPL = pages_dir ^ "/templateambigpdq3.html";;
+(* let final_results_TPL = pages_dir ^ "/templateambigpdq3.html";; *)
+let final_results_TPL = pages_dir ^ "/moogle.html";;  
+
+let my_own_url =
+ let ic = Unix.open_process_in "hostname -f" in
+ let hostname = input_line ic in
+ ignore (Unix.close_process_in ic);
+ sprintf "http://%s:%d" hostname port
+;;
 
 exception Chat_unfinished
+exception Invalid_action of string  (* invalid action for "/search" method *)
+
+let javascript_quote s =
+ let rex = Pcre.regexp "'" in
+ let rex' = Pcre.regexp "\"" in
+  Pcre.replace ~rex ~templ:"\\'"
+   (Pcre.replace ~rex:rex' ~templ:"\\\"" s)
+;;
 
   (* build a bool from a 1-character-string *)
 let bool_of_string' = function
@@ -146,27 +162,15 @@ let iter_file f = fold_file (fun _ line -> f line) ()
 
 let (title_tag_RE, choices_tag_RE, msg_tag_RE, id_to_uris_RE, id_RE,
     interpretations_RE, interpretations_labels_RE, results_RE, new_aliases_RE,
-    form_RE, variables_initialization_RE)
+    form_RE, variables_initialization_RE, search_engine_url_RE)
   =
   (Pcre.regexp "@TITLE@", Pcre.regexp "@CHOICES@", Pcre.regexp "@MSG@",
   Pcre.regexp "@ID_TO_URIS@", Pcre.regexp "@ID@",
   Pcre.regexp "@INTERPRETATIONS@", Pcre.regexp "@INTERPRETATIONS_LABELS@",
   Pcre.regexp "@RESULTS@", Pcre.regexp "@NEW_ALIASES@", Pcre.regexp "@FORM@",
-  Pcre.regexp "@VARIABLES_INITIALIZATION@")
+  Pcre.regexp "@VARIABLES_INITIALIZATION@", Pcre.regexp "@SEARCH_ENGINE_URL@")
 let server_and_port_url_RE = Pcre.regexp "^http://([^/]+)/.*$"
 
-exception NotAnInductiveDefinition
-
-let port =
-  try
-    int_of_string (Sys.getenv port_env_var)
-  with
-  | Not_found -> default_port
-  | Failure "int_of_string" ->
-      prerr_endline "Warning: invalid port, reverting to default";
-      default_port
-;;
-
 let pp_error = sprintf "<html><body><h1>Error: %s</h1></body></html>";;
 
 let bad_request body outchan =
@@ -177,44 +181,25 @@ let contype = "Content-Type", "text/html";;
 
 (* SEARCH ENGINE functions *)
 
-let refine_constraints ((constr_obj:T.r_obj list), (constr_rel:T.r_rel list), (constr_sort:T.r_sort list)) =
- function
-    "/searchPattern" ->
-      U.universe_for_search_pattern,
-       (constr_obj, constr_rel, constr_sort),
-       (Some constr_obj, Some constr_rel, Some constr_sort)
-  | "/matchConclusion" ->
-      let constr_obj' =
-       List.map
-        (function (pos, uri) -> U.set_full_position pos None, uri)
-        (List.filter
-          (function (pos, _) -> U.is_conclusion pos)
-          constr_obj)
-      in
-       U.universe_for_match_conclusion,
-       (*CSC: we must select the must constraints here!!! *)
-       (constr_obj',[],[]),(Some constr_obj', None, None)
-  | _ -> assert false
-;;
-
 let get_constraints term =
  function
-    "/locateInductivePrinciple" ->
-      let uri = 
-       match term with
-          Cic.MutInd (uri,t,_) -> MQueryUtil.string_of_uriref (uri,[t])
-        | _ -> raise NotAnInductiveDefinition
-      in
-      let constr_obj =
-       [(`InHypothesis, uri); (`MainHypothesis (Some 0), uri)]
-      in
-      let constr_rel = [`MainConclusion None] in
-      let constr_sort = [(`MainHypothesis (Some 1), T.Prop)] in
-       U.universe_for_search_pattern,
-        (constr_obj, constr_rel, constr_sort), (None,None,None)
-  | req_path ->
-     let must = CGSearchPattern.get_constraints term in
-      refine_constraints must req_path
+    | "/locateInductivePrinciple" ->
+      None,
+      (CGLocateInductive.get_constraints term),
+      (None,None,None)
+    | "/searchPattern" ->
+     let constr_obj, constr_rel, constr_sort =
+       CGSearchPattern.get_constraints term in
+     (Some CGSearchPattern.universe),
+     (constr_obj, constr_rel, constr_sort),
+     (Some constr_obj, Some constr_rel, Some constr_sort)
+    | "/matchConclusion" ->
+     let list_of_must, only = CGMatchConclusion.get_constraints [] [] term in
+(* FG: there is no way to choose the block number ***************************)
+     let block = pred (List.length list_of_must) in 
+      (Some CGMatchConclusion.universe), 
+      (List.nth list_of_must block, [], []), (Some only, None, None)
+    | _ -> assert false
 ;;
 
 (*
@@ -290,35 +275,130 @@ let add_user_constraints ~constraints
   | _ -> failwith ("Can't parse constraint string: " ^ constraints)
 in
 
+let send_results results
+  ?(id_to_uris = DisambiguatingParser.EnvironmentP3.of_string "") req outchan
+  =
+  Http_daemon.send_basic_headers ~code:200 outchan ;
+  Http_daemon.send_header "Content-Type" "text/xml" outchan;
+  Http_daemon.send_CRLF outchan ;
+  let subst =
+    (search_engine_url_RE, my_own_url) ::
+    (results_RE, theory_of_result results)::
+    (List.map
+      (function (key,value) ->
+        let key' = (Pcre.extract ~pat:"param\\.(.*)" key).(1) in
+        Pcre.regexp ("@" ^ key' ^ "@"), value)
+      (List.filter
+             (fun (key,_) as p-> Pcre.pmatch ~pat:"^param\\." key)
+             req#params))
+    in
+    iter_file
+      (fun line ->
+        let new_aliases =
+          DisambiguatingParser.EnvironmentP3.to_string id_to_uris
+        in
+        let processed_line =
+          apply_substs
+            (* CSC: Bug here: this is a string, not an array! *)
+            ((new_aliases_RE, "'" ^ javascript_quote new_aliases ^ "'")::subst) 
+            line
+        in
+        output_string outchan (processed_line ^ "\n"))
+      final_results_TPL
+in
+
 (* HTTP DAEMON CALLBACK *)
 
-let callback (req: Http_types.request) outchan =
+let build_dynamic_uri url params =
+  let p = 
+    String.concat "&" (List.map  (fun (key,value) -> (key ^ "=" ^ (Netencoding.Url.encode value))) params) in
+  url ^ "?" ^ p
+in
+
+let build_uwobo_request (req: Http_types.request) outchan =
+  prerr_endline ("ECCOLO: " ^ req#param "param.SEARCH_ENGINE_URL");
+  let xmluri = build_dynamic_uri ((req#param "param.SEARCH_ENGINE_URL") ^ "/search") req#params in
+  prerr_endline ("xmluri: " ^ xmluri);
+  (*let xmluri = Netencoding.Url.encode xmluri in*)
+  let server_and_port = req#param "param.processorURL" in
+  let newreq = 
+    build_dynamic_uri 
+      (server_and_port ^ "apply") 
+      (("xmluri",xmluri)::("keys",(req#param "param.thkeys"))::req#params) in
+  (* if List.mem server_and_port valid_servers then *)
+  prerr_endline newreq;
+  if true then 
+    Http_daemon.respond
+      ~headers:["Content-Type", "text/html"]
+      ~body:(Http_client.http_get newreq)
+      outchan
+  else
+    Http_daemon.respond
+      ~body:(pp_error ("Untrusted UWOBO server: " ^ server_and_port ^
+      (String.concat "\n" valid_servers)))
+      outchan
+in
+
+let proxy url outchan =
+  let server_and_port =
+    (Pcre.extract ~rex:server_and_port_url_RE url).(1)
+  in
+  if List.mem server_and_port valid_servers then
+    Http_daemon.respond
+      ~headers:["Content-Type", "text/html"]
+      ~body:(Http_client.http_get url)
+      outchan
+  else
+    Http_daemon.respond
+      ~body:(pp_error ("Untrusted UWOBO server: " ^ server_and_port))
+      outchan
+in
+
+let callback mqi_handle (req: Http_types.request) outchan =
   try
     debug_print (sprintf "Received request: %s" req#path);
     (match req#path with
+    | "/help" -> Http_daemon.respond ~body:"HELM Search Engine" outchan
+    | "/search" ->
+        let initial_expression =
+          try req#param "expression" with Http_types.Param_not_found _ -> ""
+        in
+        let expression =
+          Pcre.replace ~pat:"\\s*$"
+            (Pcre.replace ~pat:"^\\s*" initial_expression)
+        in
+        if expression = "" then
+          send_results [] req outchan
+        else
+          (try
+            let results =
+              match req#param "action" with
+              | "locate" ->
+                  prerr_endline ("EXPRESSION : " ^ expression);
+                  let query = G.locate expression in
+                  MQueryInterpreter.execute mqi_handle query
+              | "hint" -> failwith "NOT IMPLEMENTED"  (* TODO *)
+              | "match" -> failwith "NOT IMPLEMENTED" (* TODO *)
+              | "elim" -> failwith "NOT IMPLEMENTED"  (* TODO *)
+              | action -> raise (Invalid_action action)
+            in
+            send_results results req outchan
+          with Invalid_action action ->
+              Http_daemon.respond_error ~status:(`Client_error `Bad_request)
+                ~body:("Invalid action " ^ action) outchan)
     | "/execute" ->
-        let mqi_handle = C.init mqi_flags debug_print in 
         let query_string = req#param "query" in
         let lexbuf = Lexing.from_string query_string in
         let query = MQueryUtil.query_of_text lexbuf in
         let result = MQueryInterpreter.execute mqi_handle query in
         let result_string = pp_result result in
-             C.close mqi_handle;
         Http_daemon.respond ~body:result_string ~headers:[contype] outchan
-    | "/locate" ->
-        let mqi_handle = C.init mqi_flags debug_print in
-        let id = req#param "id" in
-        let query = G.locate id in
-       let result = MQueryInterpreter.execute mqi_handle query in
-             C.close mqi_handle;
-        Http_daemon.respond ~headers:[contype] ~body:(pp_result result) outchan
+(*  Http_daemon.respond ~headers:[contype] ~body:(pp_result result) outchan *)
     | "/unreferred" ->
-        let mqi_handle = C.init mqi_flags debug_print in
         let target = req#param "target" in
         let source = req#param "source" in
-       let query = G.unreferred target source in
-       let result = MQueryInterpreter.execute mqi_handle query in
-             C.close mqi_handle;
+        let query = G.unreferred target source in
+        let result = MQueryInterpreter.execute mqi_handle query in
         Http_daemon.respond ~headers:[contype] ~body:(pp_result result) outchan
     | "/getpage" ->
         (* TODO implement "is_permitted" *)
@@ -341,6 +421,7 @@ let callback (req: Http_types.request) outchan =
                 (fun line ->
                   output_string outchan
                     ((apply_substs
+                       ((search_engine_url_RE, my_own_url) ::
                        (List.map
                          (function (key,value) ->
                            let key' =
@@ -351,54 +432,23 @@ let callback (req: Http_types.request) outchan =
                          (List.filter
                            (fun (key,_) as p-> Pcre.pmatch ~pat:"^param\\." key)
                            req#params)
-                       )
+                       ))
                        line) ^
                     "\n"))
                 fname
             end else
               Http_daemon.send_file ~src:(FileSrc fname) outchan)
         | page -> Http_daemon.respond_forbidden ~url:page outchan))
-    | "/ask_uwobo" ->
-      let url = req#param "url" in
-      let server_and_port =
-        (Pcre.extract ~rex:server_and_port_url_RE url).(1)
-      in
-      if List.mem server_and_port valid_servers then
-        Http_daemon.respond
-          ~headers:["Content-Type", "text/html"]
-          ~body:(Http_client.Convenience.http_get url)
-          outchan
-      else
-        Http_daemon.respond
-          ~body:(pp_error ("Untrusted UWOBO server: " ^ server_and_port))
-          outchan
+    (* OLD | "/ask_uwobo" -> proxy (req#param "url") outchan *)
+    | "/ask_uwobo" -> build_uwobo_request req outchan
     | "/searchPattern"
     | "/matchConclusion"
     | "/locateInductivePrinciple" ->
-        let mqi_handle = C.init mqi_flags debug_print in
         let term_string = req#param "term" in
-        let lexbuf = Lexing.from_string term_string in
         let (context, metasenv) = ([], []) in
-        let (dom, mk_metasenv_and_expr) =
-          CicTextualParserContext.main
-            ~context ~metasenv CicTextualLexer.token lexbuf
-        in
         let id_to_uris_raw = req#param "aliases" in
-        let tokens = Pcre.split ~pat:"\\s" id_to_uris_raw in
-        let rec parse_tokens keys lookup = function (* TODO spostarla fuori *)
-          | [] -> keys, lookup
-          | "alias" :: key :: value :: rest ->
-              let key' = CicTextualParser0.Id key in
-               parse_tokens
-                 (key'::keys)
-                 (fun id ->
-                   if id = key' then
-                     Some
-                      (CicTextualParser0.Uri (MQueryMisc.cic_textual_parser_uri_of_string value))
-                   else lookup id)
-                 rest
-          | _ -> failwith "Can't parse aliases"
-        in
+        let parse_interpretation_choices choices =
+         List.map int_of_string (Pcre.split ~pat:" " choices) in
         let parse_choices choices_raw =
           let choices = Pcre.split ~pat:";" choices_raw in
           List.fold_left
@@ -407,8 +457,6 @@ let callback (req: Http_types.request) outchan =
               | ""::id::tail
               | id::tail when id<>"" ->
                   (fun id' ->
-prerr_endline ("#### " ^ id ^ " :=");
-List.iter (fun u -> prerr_endline ("<" ^ Netencoding.Url.decode u ^ ">")) tail;
                     if id = id' then
                       Some (List.map (fun u -> Netencoding.Url.decode u) tail)
                     else
@@ -417,25 +465,23 @@ List.iter (fun u -> prerr_endline ("<" ^ Netencoding.Url.decode u ^ ">")) tail;
             (fun _ -> None)
             choices
         in
-        let (id_to_uris : Disambiguate.domain_and_interpretation) =
-         parse_tokens [] (fun _ -> None) tokens in
+        let id_to_uris =
+         DisambiguatingParser.EnvironmentP3.of_string id_to_uris_raw in
         let id_to_choices =
           try
             let choices_raw = req#param "choices" in
             parse_choices choices_raw
           with Http_types.Param_not_found _ -> (fun _ -> None)
         in
-        let module Chat: Disambiguate.Callbacks =
+        let interpretation_choices =
+          try
+            let choices_raw = req#param "interpretation_choices" in
+            Some (parse_interpretation_choices choices_raw)
+          with Http_types.Param_not_found _ -> None
+        in
+        let module Chat: DisambiguateTypes.Callbacks =
           struct
 
-            let get_metasenv () =
-             !CicTextualParser0.metasenv
-
-            let set_metasenv metasenv =
-              CicTextualParser0.metasenv := metasenv
-
-            let output_html = prerr_endline
-
             let interactive_user_uri_choice
               ~selection_mode ?ok
               ?enable_button_for_non_vars ~(title: string) ~(msg: string)
@@ -447,7 +493,7 @@ List.iter (fun u -> prerr_endline ("<" ^ Netencoding.Url.decode u ^ ">")) tail;
                   let msg = Pcre.replace ~pat:"\'" ~templ:"\\\'" msg in
                   (match selection_mode with
                   | `SINGLE -> assert false
-                  | `EXTENDED ->
+                  | `MULTIPLE ->
                       Http_daemon.send_basic_headers ~code:200 outchan ;
                       Http_daemon.send_CRLF outchan ;
                       iter_file
@@ -470,121 +516,31 @@ List.iter (fun u -> prerr_endline ("<" ^ Netencoding.Url.decode u ^ ">")) tail;
                       raise Chat_unfinished))
 
             let interactive_interpretation_choice interpretations =
-              let html_interpretations_labels =
-                String.concat ", "
-                  (List.map
-                    (fun l ->
-                      "\'" ^
-                      (String.concat "<br />"
-                        (List.map
-                          (fun (id, value) ->
-                            (sprintf "alias %s %s" id value))
-                          l)) ^
-                      "\'")
-                  interpretations)
-              in
-              let html_interpretations =
-                String.concat ", "
-                  (List.map
-                    (fun l ->
-                      "\'" ^
-                      (String.concat " "
-                        (List.map
-                          (fun (id, value) ->
-                            (sprintf "alias %s %s"
-                              id
-                              (MQueryMisc.wrong_xpointer_format_from_wrong_xpointer_format'
-                                value)))
-                          l)) ^
-                      "\'")
+             match interpretation_choices with
+                Some l -> prerr_endline "CARRAMBA" ; l
+              | None ->
+                let html_interpretations_labels =
+                  String.concat ", "
+                    (List.map
+                      (fun l ->
+                        "\'" ^
+                        (String.concat "<br />"
+                          (List.map
+                            (fun (id, value) ->
+                              let id = javascript_quote id in
+                              let value = javascript_quote value in
+                               sprintf "%s = %s" id value)
+                            l)) ^
+                        "\'")
                     interpretations)
-              in
-              Http_daemon.send_basic_headers ~code:200 outchan ;
-              Http_daemon.send_CRLF outchan ;
-              iter_file
-                (fun line ->
-                  let processed_line =
-                    apply_substs
-                      [interpretations_RE, html_interpretations;
-                       interpretations_labels_RE, html_interpretations_labels]
-                      line
-                  in
-                  output_string outchan (processed_line ^ "\n"))
-                interactive_interpretation_choice_TPL;
-              raise Chat_unfinished
-
-            let input_or_locate_uri ~title =
-              UriManager.uri_of_string "cic:/Coq/Init/DataTypes/nat_ind.con"
-
-          end
-        in
-        let module Disambiguate' = Disambiguate.Make (Chat) in
-        let (id_to_uris', metasenv', term') =
-          Disambiguate'.disambiguate_input mqi_handle
-            context metasenv dom mk_metasenv_and_expr id_to_uris
-        in
-        (match metasenv' with
-        | [] ->
-            let universe,
-                ((must_obj, must_rel, must_sort) as must'),
-                ((only_obj, only_rel, only_sort) as only) =
-              get_constraints term' req#path
-            in
-            let must'', only' =
-              (try
-                add_user_constraints
-                  ~constraints:(req#param "constraints")
-                  (must', only)
-              with Http_types.Param_not_found _ ->
-                let variables =
-                 "var aliases = '" ^ id_to_uris_raw ^ "';\n" ^
-                 "var constr_obj_len = " ^
-                  string_of_int (List.length must_obj) ^ ";\n" ^
-                 "var constr_rel_len = " ^
-                  string_of_int (List.length must_rel) ^ ";\n" ^
-                 "var constr_sort_len = " ^
-                  string_of_int (List.length must_sort) ^ ";\n" in
-                let form =
-                  (if must_obj = [] then "" else
-                    "<h4>Obj constraints</h4>" ^
-                    "<table>" ^
-                    (String.concat "\n" (List.map html_of_r_obj must_obj)) ^
-                    "</table>" ^
-                    (* The following three lines to make Javascript create *)
-                    (* the constr_obj[] and obj_depth[] arrays even if we  *)
-                    (* have only one real entry.                           *)
-                    "<input type=\"hidden\" name=\"constr_obj\" />" ^
-                    "<input type=\"hidden\" name=\"obj_depth\" />") ^
-                  (if must_rel = [] then "" else
-                   "<h4>Rel constraints</h4>" ^
-                   "<table>" ^
-                   (String.concat "\n" (List.map html_of_r_rel must_rel)) ^
-                   "</table>" ^
-                    (* The following two lines to make Javascript create *)
-                    (* the constr_rel[] and rel_depth[] arrays even if   *)
-                    (* we have only one real entry.                      *)
-                    "<input type=\"hidden\" name=\"constr_rel\" />" ^
-                    "<input type=\"hidden\" name=\"rel_depth\" />") ^
-                  (if must_sort = [] then "" else
-                    "<h4>Sort constraints</h4>" ^
-                    "<table>" ^
-                    (String.concat "\n" (List.map html_of_r_sort must_sort)) ^
-                    "</table>" ^
-                    (* The following two lines to make Javascript create *)
-                    (* the constr_sort[] and sort_depth[] arrays even if *)
-                    (* we have only one real entry.                      *)
-                    "<input type=\"hidden\" name=\"constr_sort\" />" ^
-                    "<input type=\"hidden\" name=\"sort_depth\" />") ^
-                    "<h4>Only constraints</h4>" ^
-                    "Enforce Only constraints for objects: " ^
-                      "<input type='checkbox' name='only_obj'" ^
-                      (if only_obj = None then "" else " checked='yes'") ^ " /><br />" ^
-                    "Enforce Rel constraints for objects: " ^
-                      "<input type='checkbox' name='only_rel'" ^
-                      (if only_rel = None then "" else " checked='yes'") ^ " /><br />" ^
-                    "Enforce Sort constraints for objects: " ^
-                      "<input type='checkbox' name='only_sort'" ^
-                      (if only_sort = None then "" else " checked='yes'") ^ " /><br />"
+                in
+                let html_interpretations =
+                 let rec aux n =
+                  function
+                     [] -> []
+                   | _::tl -> ("'" ^ string_of_int n ^ "'")::(aux (n+1) tl)
+                 in
+                  String.concat ", " (aux 0 interpretations)
                 in
                 Http_daemon.send_basic_headers ~code:200 outchan ;
                 Http_daemon.send_CRLF outchan ;
@@ -592,53 +548,107 @@ List.iter (fun u -> prerr_endline ("<" ^ Netencoding.Url.decode u ^ ">")) tail;
                   (fun line ->
                     let processed_line =
                       apply_substs
-                       [form_RE, form ;
-                        variables_initialization_RE, variables] line
+                        [interpretations_RE, html_interpretations;
+                         interpretations_labels_RE, html_interpretations_labels]
+                        line
                     in
                     output_string outchan (processed_line ^ "\n"))
-                  constraints_choice_TPL;
-                  raise Chat_unfinished)
-            in
-            let query =
-             G.query_of_constraints (Some universe) must'' only'
-            in
-                 let results = MQueryInterpreter.execute mqi_handle query in 
-             Http_daemon.send_basic_headers ~code:200 outchan ;
-             Http_daemon.send_CRLF outchan ;
-             iter_file
-               (fun line ->
-                 let new_aliases =
-                   match id_to_uris' with
-                   | (domain, f) ->
-                       String.concat ", "
-                         (List.map
-                           (fun name ->
-                             sprintf "\'alias %s cic:%s\'"
-                               (match name with
-                                   CicTextualParser0.Id name -> name
-                                 | _ -> assert false (*CSC: completare *))
-                               (match f name with
-                               | None -> assert false
-                               | Some (CicTextualParser0.Uri t) ->
-                                   MQueryMisc.string_of_cic_textual_parser_uri
-                                     t
-                               | _ -> assert false (*CSC: completare *)))
-                           domain)
-                 in
-                 let processed_line =
-                   apply_substs
-                     [results_RE, theory_of_result results ;
-                      new_aliases_RE, new_aliases]
-                     line
-                 in
-                 output_string outchan (processed_line ^ "\n"))
-               final_results_TPL
-        | _ -> (* unable to instantiate some implicit variable *)
-            Http_daemon.respond
-              ~headers:[contype]
-              ~body:"some implicit variables are still unistantiated :-("
-              outchan);
-            C.close mqi_handle
+                  interactive_interpretation_choice_TPL;
+                raise Chat_unfinished
+
+            let input_or_locate_uri ~title ?id () =
+             assert false
+
+          end
+        in
+        let module Disambiguate' = DisambiguatingParser.Make(Chat) in
+        let (id_to_uris', metasenv', term') =
+         match
+          Disambiguate'.disambiguate_term mqi_handle
+            context metasenv term_string id_to_uris
+         with
+            [id_to_uris',metasenv',term'] -> id_to_uris',metasenv',term'
+          | _ -> assert false
+        in
+          let universe,
+              ((must_obj, must_rel, must_sort) as must'),
+              ((only_obj, only_rel, only_sort) as only) =
+            get_constraints term' req#path
+          in
+          let must'', only' =
+            (try
+              add_user_constraints
+                ~constraints:(req#param "constraints")
+                (must', only)
+            with Http_types.Param_not_found _ ->
+              let variables =
+               "var aliases = '" ^ id_to_uris_raw ^ "';\n" ^
+               "var constr_obj_len = " ^
+                string_of_int (List.length must_obj) ^ ";\n" ^
+               "var constr_rel_len = " ^
+                string_of_int (List.length must_rel) ^ ";\n" ^
+               "var constr_sort_len = " ^
+                string_of_int (List.length must_sort) ^ ";\n" in
+              let form =
+                (if must_obj = [] then "" else
+                  "<h4>Obj constraints</h4>" ^
+                  "<table>" ^
+                  (String.concat "\n" (List.map html_of_r_obj must_obj)) ^
+                  "</table>" ^
+                  (* The following three lines to make Javascript create *)
+                  (* the constr_obj[] and obj_depth[] arrays even if we  *)
+                  (* have only one real entry.                           *)
+                  "<input type=\"hidden\" name=\"constr_obj\" />" ^
+                  "<input type=\"hidden\" name=\"obj_depth\" />") ^
+                (if must_rel = [] then "" else
+                 "<h4>Rel constraints</h4>" ^
+                 "<table>" ^
+                 (String.concat "\n" (List.map html_of_r_rel must_rel)) ^
+                 "</table>" ^
+                  (* The following two lines to make Javascript create *)
+                  (* the constr_rel[] and rel_depth[] arrays even if   *)
+                  (* we have only one real entry.                      *)
+                  "<input type=\"hidden\" name=\"constr_rel\" />" ^
+                  "<input type=\"hidden\" name=\"rel_depth\" />") ^
+                (if must_sort = [] then "" else
+                  "<h4>Sort constraints</h4>" ^
+                  "<table>" ^
+                  (String.concat "\n" (List.map html_of_r_sort must_sort)) ^
+                  "</table>" ^
+                  (* The following two lines to make Javascript create *)
+                  (* the constr_sort[] and sort_depth[] arrays even if *)
+                  (* we have only one real entry.                      *)
+                  "<input type=\"hidden\" name=\"constr_sort\" />" ^
+                  "<input type=\"hidden\" name=\"sort_depth\" />") ^
+                  "<h4>Only constraints</h4>" ^
+                  "Enforce Only constraints for objects: " ^
+                    "<input type='checkbox' name='only_obj'" ^
+                    (if only_obj = None then "" else " checked='yes'") ^ " /><br />" ^
+                  "Enforce Rel constraints for objects: " ^
+                    "<input type='checkbox' name='only_rel'" ^
+                    (if only_rel = None then "" else " checked='yes'") ^ " /><br />" ^
+                  "Enforce Sort constraints for objects: " ^
+                    "<input type='checkbox' name='only_sort'" ^
+                    (if only_sort = None then "" else " checked='yes'") ^ " /><br />"
+              in
+              Http_daemon.send_basic_headers ~code:200 outchan ;
+              Http_daemon.send_CRLF outchan ;
+              iter_file
+                (fun line ->
+                  let processed_line =
+                    apply_substs
+                     [form_RE, form ;
+                      variables_initialization_RE, variables] line
+                  in
+                  output_string outchan (processed_line ^ "\n"))
+                constraints_choice_TPL;
+                raise Chat_unfinished)
+          in
+          let query =
+           G.query_of_constraints universe must'' only'
+          in
+          let results = MQueryInterpreter.execute mqi_handle query in 
+          send_results results ~id_to_uris:id_to_uris' req outchan
     | invalid_request ->
         Http_daemon.respond_error ~status:(`Client_error `Bad_request) outchan);
     debug_print (sprintf "%s done!" req#path)
@@ -647,15 +657,16 @@ List.iter (fun u -> prerr_endline ("<" ^ Netencoding.Url.decode u ^ ">")) tail;
   | Http_types.Param_not_found attr_name ->
       bad_request (sprintf "Parameter '%s' is missing" attr_name) outchan
   | exc ->
-      Http_daemon.respond
-        ~body:(pp_error ("Uncaught exception: " ^ (Printexc.to_string exc)))
-        outchan
+      let msg = sprintf "Uncaught exception: %s" (Printexc.to_string exc) in
+       debug_print msg ;
+       Http_daemon.respond ~body:(pp_error msg) outchan
 in
 printf "%s started and listening on port %d\n" daemon_name port;
 printf "Current directory is %s\n" (Sys.getcwd ());
 printf "HTML directory is %s\n" pages_dir;
 flush stdout;
 Unix.putenv "http_proxy" "";
-Http_daemon.start' ~port callback;
+let mqi_handle = C.init ~log:debug_print () in
+Http_daemon.start' ~port (callback mqi_handle);
+C.close mqi_handle;
 printf "%s is terminating, bye!\n" daemon_name
-