]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/mathql_generator/cGSearchPattern.ml
ocaml 3.09 transition
[helm.git] / helm / ocaml / mathql_generator / cGSearchPattern.ml
index a56d65959448421f872acc554e00edb194359ab8..47345e9f3bd079d9e84572224bb5848195f7e573 100644 (file)
@@ -80,7 +80,8 @@ let get_constraints term =
   let rec process_type_aux kind =
    function
       C.Var (uri,expl_named_subst) ->
-       ([!!!kind, UriManager.string_of_uri uri],[],[]) @@
+       (* andrea: this is a bug: variable are not indexedin the db 
+         ([!!!kind, UriManager.string_of_uri uri],[],[]) @@ *)
          (process_type_aux_expl_named_subst kind expl_named_subst)
     | C.Rel _ ->
        (match kind with
@@ -95,13 +96,13 @@ let get_constraints term =
              match s with
                 Cic.Prop -> T.Prop
               | Cic.Set -> T.Set
-              | Cic.Type -> T.Type
+              | Cic.Type _ -> T.Type (* TASSI: ?? *)
              | Cic.CProp -> T.CProp
             in
             [],[],[!!kind,s']
          | _ -> [],[],[])
-    | C.Meta _
-    | C.Implicit -> assert false
+    | C.Meta _ -> [],[],[] (* ???? To be understood *)
+    | C.Implicit -> assert false
     | C.Cast (te,_) ->
        (* type ignored *)
        process_type_aux kind te
@@ -171,6 +172,7 @@ in
 ;;
 
 (*CSC: Debugging only *)
+(* 
 let get_constraints term =
  let res = get_constraints term in
  let (objs,rels,sorts) = res in
@@ -187,7 +189,7 @@ let get_constraints term =
    (function (p, s) -> prerr_endline (text_of_pos (p:>T.full_position) ^ " " ^ U.text_of_sort s)
    ) sorts ;
   res
-;;
+;; *)
 
 let universe =
    [T.MainHypothesis; T.InHypothesis; T.MainConclusion; T.InConclusion]