]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/cic_proof_checking/cicTypeChecker.ml
first moogle template checkin
[helm.git] / helm / ocaml / cic_proof_checking / cicTypeChecker.ml
index c4d62986e100a84f7800a6cc99beaaf75179ebc8..36bfb28b19cd22c77c7471ec5343dab140f20861 100644 (file)
@@ -793,11 +793,12 @@ and guarded_by_destructors context n nn kl x safes =
  let module U = UriManager in
   function
      C.Rel m when m > n && m <= nn -> false
-   | C.Rel n ->
+   | C.Rel m ->
       (match List.nth context (n-1) with
           Some (_,C.Decl _) -> true
         | Some (_,C.Def (bo,_)) ->
-           guarded_by_destructors context n nn kl x safes bo
+           guarded_by_destructors context m nn kl x safes
+            (CicSubstitution.lift m bo)
        | None -> raise (TypeCheckerFailure "Reference to deleted hypothesis")
       )
    | C.Meta _
@@ -1173,7 +1174,8 @@ and check_allowed_sort_elimination context uri i need_dummy ind arity1 arity2 =
    | (C.Sort C.Prop, C.Sort C.Prop) when need_dummy -> true
    | (C.Sort C.Prop, C.Sort C.Set)
    | (C.Sort C.Prop, C.Sort C.CProp)
-   | (C.Sort C.Prop, C.Sort C.Type) when need_dummy ->
+   | (C.Sort C.Prop, C.Sort (C.Type _) ) when need_dummy ->
+   (* TASSI: da verificare *)
 (*CSC: WRONG. MISSING CONDITIONS ON THE ARGUMENTS OF THE CONSTRUTOR *)
        (match CicEnvironment.get_obj uri with
            C.InductiveDefinition (itl,_,_) ->
@@ -1190,7 +1192,8 @@ and check_allowed_sort_elimination context uri i need_dummy ind arity1 arity2 =
    | (C.Sort C.Set, C.Sort C.CProp) when need_dummy -> true
    | (C.Sort C.CProp, C.Sort C.Set) when need_dummy -> true
    | (C.Sort C.CProp, C.Sort C.CProp) when need_dummy -> true
-   | ((C.Sort C.Set, C.Sort C.Type) | (C.Sort C.CProp, C.Sort C.Type))
+   | ((C.Sort C.Set, C.Sort (C.Type _)) | (C.Sort C.CProp, C.Sort (C.Type _)))
+      (* TASSI: da verificare *)
       when need_dummy ->
        (match CicEnvironment.get_obj uri with
            C.InductiveDefinition (itl,_,paramsno) ->
@@ -1204,7 +1207,8 @@ and check_allowed_sort_elimination context uri i need_dummy ind arity1 arity2 =
             raise (TypeCheckerFailure ("Unknown mutual inductive definition:" ^
               UriManager.string_of_uri uri))
        )
-   | (C.Sort C.Type, C.Sort _) when need_dummy -> true
+   | (C.Sort (C.Type _), C.Sort _) when need_dummy -> true
+     (* TASSI: da verificare *)
    | (C.Sort C.Prop, C.Prod (name,so,ta)) when not need_dummy ->
        let res = CicReduction.are_convertible context so ind
        in
@@ -1233,7 +1237,8 @@ and check_allowed_sort_elimination context uri i need_dummy ind arity1 arity2 =
             C.Sort C.Prop
           | C.Sort C.Set  -> true
          | C.Sort C.CProp -> true
-          | C.Sort C.Type ->
+          | C.Sort (C.Type _) ->
+           (* TASSI: da verificare *)
              (match CicEnvironment.get_obj uri with
                  C.InductiveDefinition (itl,_,paramsno) ->
                   let (_,_,_,cl) = List.nth itl i in
@@ -1250,7 +1255,8 @@ and check_allowed_sort_elimination context uri i need_dummy ind arity1 arity2 =
              )
           | _ -> raise (AssertFailure "19")
         )
-   | (C.Sort C.Type, C.Prod (_,so,_)) when not need_dummy ->
+   | (C.Sort (C.Type _), C.Prod (_,so,_)) when not need_dummy ->
+     (* TASSI: da verificare *)
        CicReduction.are_convertible context so ind
    | (_,_) -> false
   
@@ -1356,7 +1362,15 @@ and type_of_aux' metasenv context t =
        let (_,canonical_context,ty) = CicUtil.lookup_meta n metasenv in
         check_metasenv_consistency metasenv context canonical_context l;
         CicSubstitution.lift_meta l ty
-    | C.Sort s -> C.Sort C.Type (*CSC manca la gestione degli universi!!! *)
+      (* TASSI: CONSTRAINTS *)
+    | C.Sort (C.Type t) -> 
+       let t' = CicUniv.fresh() in
+        if not (CicUniv.add_gt t' t ) then
+         assert false (* t' is fresh! an error in CicUniv *)
+       else
+          C.Sort (C.Type t')
+      (* TASSI: CONSTRAINTS *)
+    | C.Sort s -> C.Sort (C.Type (CicUniv.fresh ()))
     | C.Implicit _ -> raise (AssertFailure "21")
     | C.Cast (te,ty) as t ->
        let _ = type_of_aux context ty in
@@ -1622,7 +1636,7 @@ in if not res then debug_print ("#### " ^ CicPp.ppterm (type_of_aux context p) ^
          | Cic.Variable (_,None,_,_) -> ()
          | _ ->
             raise (TypeCheckerFailure
-              ("Unknown mutual inductive definition:" ^
+              ("Unknown variable definition:" ^
               UriManager.string_of_uri uri))
        ) ;
        let typeoft = type_of_aux context t in
@@ -1645,9 +1659,18 @@ in if not res then debug_print ("#### " ^ CicPp.ppterm (type_of_aux context p) ^
    let t2' = CicReduction.whd ((Some (name,C.Decl s))::context) t2 in
    match (t1', t2') with
       (C.Sort s1, C.Sort s2)
-        when (s2 = C.Prop or s2 = C.Set or s2 = C.CProp) -> (* different from Coq manual!!! *)
+        when (s2 = C.Prop or s2 = C.Set or s2 = C.CProp) -> 
+        (* different from Coq manual!!! *)
          C.Sort s2
-    | (C.Sort s1, C.Sort s2) -> C.Sort C.Type (*CSC manca la gestione degli universi!!! *)
+    | (C.Sort (C.Type t1), C.Sort (C.Type t2)) -> 
+      (* TASSI: CONSRTAINTS: the same in doubletypeinference, cicrefine *)
+       let t' = CicUniv.fresh() in
+       if not (CicUniv.add_ge t' t1) || not (CicUniv.add_ge t' t2) then
+         assert false ; (* not possible, error in CicUniv *)
+       C.Sort (C.Type t')
+    | (C.Sort _,C.Sort (C.Type t1)) -> 
+        (* TASSI: CONSRTAINTS: the same in doubletypeinference, cicrefine *)
+       C.Sort (C.Type t1) (* c'e' bisogno di un fresh? *)
     | (C.Meta _, C.Sort _) -> t2'
     | (C.Meta _, (C.Meta (_,_) as t))
     | (C.Sort _, (C.Meta (_,_) as t)) when CicUtil.is_closed t ->
@@ -1664,7 +1687,7 @@ in if not res then debug_print ("#### " ^ CicPp.ppterm (type_of_aux context p) ^
    | (hete, hety)::tl ->
     (match (CicReduction.whd context hetype) with
         Cic.Prod (n,s,t) ->
-         if CicReduction.are_convertible context s hety then
+         if CicReduction.are_convertible context hety s then
           (CicReduction.fdebug := -1 ;
            eat_prods context (CicSubstitution.subst hete t) tl
           )