]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/cic_textual_parser/cicTextualParser.mly
Universes introduction
[helm.git] / helm / ocaml / cic_textual_parser / cicTextualParser.mly
index 84e0f0ee50bcc4f90808fac592323016252e8863..a869bc0689f1d4ecf1960504ac7ac58b2ce42bf3 100644 (file)
  ;;
 
  let mk_implicit () =
+  let newuniv = CicUniv.fresh () in
+  (* TASSI: what is an implicit? *)
   let newmeta = new_meta () in
    let new_canonical_context = [] in
     let irl =
      identity_relocation_list_for_metavariable new_canonical_context
     in
      CicTextualParser0.metasenv :=
-      [newmeta, new_canonical_context, Sort Type ;
+      [newmeta, new_canonical_context, Sort (Type newuniv);
        newmeta+1, new_canonical_context, Meta (newmeta,irl);
        newmeta+2, new_canonical_context, Meta (newmeta+1,irl)
       ] @ !CicTextualParser0.metasenv ;
@@ -288,7 +290,7 @@ expr2:
     { mk_implicit () }
  | SET   { [], function _ -> Sort Set }
  | PROP  { [], function _ -> Sort Prop }
- | TYPE  { [], function _ -> Sort Type }
+ | TYPE  { [], function _ -> Sort (Type (CicUniv.fresh ())) (* TASSI: ?? *)}
  | CPROP { [], function _ -> Sort CProp }
  | LPAREN expr CAST expr RPAREN
     { let dom1,mk_expr1 = $2 in
@@ -425,12 +427,14 @@ pihead:
  | PROD ID DOT
     { CicTextualParser0.binders := (Some (Name $2))::!CicTextualParser0.binders;
       let newmeta = new_meta () in
+      let newuniv = CicUniv.fresh () in 
        let new_canonical_context = [] in
         let irl =
          identity_relocation_list_for_metavariable new_canonical_context
         in
          CicTextualParser0.metasenv :=
-          [newmeta, new_canonical_context, Sort Type ;
+          [newmeta, new_canonical_context, Sort (Type newuniv);
+          (* TASSI: ?? *)
            newmeta+1, new_canonical_context, Meta (newmeta,irl)
           ] @ !CicTextualParser0.metasenv ;
          Cic.Name $2, ([], function _ -> Meta (newmeta+1,irl))
@@ -445,12 +449,14 @@ lambdahead:
  | LAMBDA ID DOT
     { CicTextualParser0.binders := (Some (Name $2))::!CicTextualParser0.binders;
       let newmeta = new_meta () in
+      let newuniv = CicUniv.fresh () in 
        let new_canonical_context = [] in
         let irl =
          identity_relocation_list_for_metavariable new_canonical_context
         in
          CicTextualParser0.metasenv :=
-          [newmeta, new_canonical_context, Sort Type ;
+          [newmeta, new_canonical_context, Sort (Type newuniv);
+          (* TASSI: ?? *)
            newmeta+1, new_canonical_context, Meta (newmeta,irl)
           ] @ !CicTextualParser0.metasenv ;
          Cic.Name $2, ([], function _ -> Meta (newmeta+1,irl))