]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/tactics/tacticChaser.ml
- new generated query "unreferred" implemented at server side
[helm.git] / helm / ocaml / tactics / tacticChaser.ml
index 6f83c3fd67bb726d95fae43fe24e8fbada6b1f52..f248735df91f609b36bc8e1ec44ee0004fd4390d 100644 (file)
 (*                                                                            *)
 (******************************************************************************)
 
+module I = MQueryInterpreter
+module U = MQGUtil
+module G = MQueryGenerator
+
   (* search arguments on which Apply tactic doesn't fail *)
-let searchPattern mqi_handle ?(output_html = (fun _ -> ())) ~choose_must () ~status =
+let matchConclusion mqi_handle ?(output_html = (fun _ -> ())) ~choose_must () ~status =
  let ((_, metasenv, _, _), metano) = status in
  let (_, ey ,ty) = List.find (function (m,_,_) -> m=metano) metasenv in
-  let list_of_must,only = MQueryLevels.out_restr metasenv ey ty in
+  let list_of_must, only = CGMatchConclusion.get_constraints metasenv ey ty in
   let must = choose_must list_of_must only in
-  let torigth_restriction (u,b) =
-   let p =
-    if b then
-     "http://www.cs.unibo.it/helm/schemas/schema-helm#MainConclusion" 
-    else
-     "http://www.cs.unibo.it/helm/schemas/schema-helm#InConclusion"
-    in
-    (u,p,None)
-  in
-  let rigth_must = List.map torigth_restriction must in
-  let rigth_only = Some (List.map torigth_restriction only) in
   let result =
-        MQueryInterpreter.execute mqi_handle 
-           (MQueryGenerator.query_of_constraints None
-               (rigth_must,[],[]) (rigth_only,None,None)) in 
+        I.execute mqi_handle 
+           (G.query_of_constraints
+        (Some U.universe_for_match_conclusion)
+        (must,[],[]) (Some only,None,None)) in 
        let uris =
         List.map
                (function uri,_ ->