]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/cic_disambiguation/disambiguate.ml
Universes introduction
[helm.git] / helm / ocaml / cic_disambiguation / disambiguate.ml
index 6a6ab9b274333529b8df915bb40f09fee54baa5f..139a6417a3c33c6f6f4fb4328794ac4802a5195c 100644 (file)
@@ -57,8 +57,7 @@ let refine metasenv context term =
     | CicRefine.Uncertain _ ->
         debug_print ("%%% UNCERTAIN!!! " ^ CicPp.ppterm term) ;
         Uncertain
-    | _ ->
-        (* TODO we should catch only the RefineFailure excecption *)
+    | CicRefine.RefineFailure _ ->
         debug_print ("%%% PRUNED!!! " ^ CicPp.ppterm term) ;
         Ko
 
@@ -258,7 +257,7 @@ let interpretate ~context ~env ast =
         Cic.Meta (index, cic_subst)
     | CicAst.Sort `Prop -> Cic.Sort Cic.Prop
     | CicAst.Sort `Set -> Cic.Sort Cic.Set
-    | CicAst.Sort `Type -> Cic.Sort Cic.Type
+    | CicAst.Sort `Type -> Cic.Sort (Cic.Type (CicUniv.fresh())) (* TASSI *)
     | CicAst.Sort `CProp -> Cic.Sort Cic.CProp
     | CicAst.Symbol (symbol, instance) ->
         resolve env (Symbol (symbol, instance)) ()
@@ -404,13 +403,6 @@ module Make (C: Callbacks) =
        (function uri,_ ->
          MQueryMisc.wrong_xpointer_format_from_wrong_xpointer_format' uri
        ) result in
-      HelmLogger.log (`Msg (`T "Locate query:"));
-      MQueryUtil.text_of_query
-       (fun s -> HelmLogger.log ~append_NL:false (`Msg (`T s)))
-       "" query; 
-      HelmLogger.log (`Msg (`T "Result:"));
-      MQueryUtil.text_of_result
-        (fun s -> HelmLogger.log (`Msg (`T s))) "" result;
       let uris' =
        match uris with
         | [] ->