]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/cic_transformations/content_expressions.ml
ocaml 3.09 transition
[helm.git] / helm / ocaml / cic_transformations / content_expressions.ml
index 8c88fd01f1186362a7260c1499c2f56b1eb92fa3..65216f5d6a1677ce8f943150601fce54184e720d 100644 (file)
@@ -292,11 +292,12 @@ let string_of_sort =
 
 let get_constructors uri i =
   let inductive_types =
-    (match CicEnvironment.get_obj uri with
-         Cic.Constant _ -> assert false
-     | Cic.Variable _ -> assert false
-     | Cic.CurrentProof _ -> assert false
-     | Cic.InductiveDefinition (l,_,_) -> l 
+    (let o,_ = CicEnvironment.get_obj uri CicUniv.empty_ugraph in 
+       match o with
+           Cic.Constant _ -> assert false
+        | Cic.Variable _ -> assert false
+        | Cic.CurrentProof _ -> assert false
+        | Cic.InductiveDefinition (l,_,_) -> l 
     ) in
    let (_,_,_,constructors) = List.nth inductive_types i in
    constructors
@@ -370,7 +371,8 @@ let acic2cexpr ids_to_inner_sorts t =
           make_subst subst, Some uri_str)::List.map acic2cexpr tl)) 
     | C.AAppl (aid,C.AMutInd (sid,uri,i,subst)::tl) ->
         let inductive_types = 
-          (match CicEnvironment.get_obj uri with
+          (let o,_ = CicEnvironment.get_obj uri CicUniv.empty_ugraph in 
+           match o with
              Cic.Constant _ -> assert false
            | Cic.Variable _ -> assert false
            | Cic.CurrentProof _ -> assert false
@@ -398,7 +400,8 @@ let acic2cexpr ids_to_inner_sorts t =
             make_subst subst, Some (UriManager.string_of_uri uri)))
     | C.AMutInd (id,uri,i,subst) ->
         let inductive_types = 
-          (match CicEnvironment.get_obj uri with
+          (let o,_ = CicEnvironment.get_obj uri CicUniv.empty_ugraph in
+           match o with
              Cic.Constant _ -> assert false
            | Cic.Variable _ -> assert false
            | Cic.CurrentProof _ -> assert false