]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/cic/cic.ml
first moogle template checkin
[helm.git] / helm / ocaml / cic / cic.ml
index 6d58e6164336dbb8fecf6a5e8007f5ef77b31bae..f9e99260d52944640d65ace9d5d9b6909be8cd42 100644 (file)
@@ -39,6 +39,8 @@
 type id = string  (* the abstract type of the (annotated) node identifiers *)
 type 'term explicit_named_substitution = (UriManager.uri * 'term) list
 
+type implicit_annotation = [ `Closed | `Type ]
+
 type anntarget =
    Object of annobj         (* if annobj is a Constant, this is its type *)
  | ConstantBody of annobj
@@ -50,7 +52,8 @@ type anntarget =
 and sort =
    Prop
  | Set
- | Type
+ | Type of CicUniv.universe
+ | CProp
 and name =
    Name of string
  | Anonymous
@@ -61,7 +64,7 @@ and term =
  | Meta of int * (term option) list                 (* numeric id,    *)
                                                     (*  local context *)
  | Sort of sort                                     (* sort *)
- | Implicit                                         (* *)
+ | Implicit of implicit_annotation option           (* *)
  | Cast of term * term                              (* value, type *)
  | Prod of name * term * term                       (* binder, source, target *)
  | Lambda of name * term * term                     (* binder, source, target *)
@@ -81,8 +84,8 @@ and term =
     int *                                           (*  ind. typeno,         *)
     term * term *                                   (*  outtype, ind. term   *)
     term list                                       (*  patterns             *)
- | Fix of int * inductiveFun list                   (* funno, functions *)
- | CoFix of int * coInductiveFun list               (* funno, functions *)
+ | Fix of int * inductiveFun list                   (* funno (0 based), funs *)
+ | CoFix of int * coInductiveFun list               (* funno (0 based), funs *)
 and obj =
    Constant of string * term option * term *      (* id, body, type,          *)
     UriManager.uri list                           (*  parameters              *)
@@ -122,7 +125,7 @@ and annterm =
  | AMeta of id * int * (annterm option) list        (* numeric id,    *)
                                                     (*  local context *)
  | ASort of id * sort                               (* sort *)
- | AImplicit of id                                  (* *)
+ | AImplicit of id * implicit_annotation option     (* *)
  | ACast of id * annterm * annterm                  (* value, type *)
  | AProd of id * name * annterm * annterm           (* binder, source, target *)
  | ALambda of id * name * annterm * annterm         (* binder, source, target *)