]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/cic/cic.ml
ocaml 3.09 transition
[helm.git] / helm / ocaml / cic / cic.ml
index ba51157ff9f4aa24464733c0820f0b518e4d7119..aacaabda95490e4f9e1cfc9df946f6be70e08c8c 100644 (file)
@@ -53,6 +53,15 @@ type name =
  | Name of string
  | Anonymous
 
+type object_flavour =
+  [ `Definition
+  | `Fact
+  | `Lemma
+  | `Remark
+  | `Theorem
+  | `Variant
+  ]
+
 type object_class =
   [ `Coercion
   | `Elim of sort   (** elimination principle; if sort is Type, the universe is
@@ -64,6 +73,7 @@ type object_class =
 
 type attribute =
   [ `Class of object_class
+  | `Flavour of object_flavour 
   | `Generated
   ]
 
@@ -101,7 +111,7 @@ and obj =
     UriManager.uri list * attribute list          (*  parameters              *)
  | Variable of string * term option * term *      (* name, body, type         *)
     UriManager.uri list * attribute list          (* parameters               *)
- | CurrentProof of string * metasenv * term *     (* name, conjectures, value,*)
+ | CurrentProof of string * metasenv * term *     (* name, conjectures, body, *)
     term * UriManager.uri list * attribute list   (*  type, parameters        *)
  | InductiveDefinition of inductiveType list *    (* inductive types,         *)
     UriManager.uri list * int * attribute list    (*  params, left params no  *)
@@ -169,7 +179,7 @@ and annobj =
     UriManager.uri list * attribute list            (*  parameters      *)
  | ACurrentProof of id * id *
     string * annmetasenv *                          (*  name, conjectures,    *)
-    annterm * annterm * UriManager.uri list *       (*  value,type,parameters *)
+    annterm * annterm * UriManager.uri list *       (*  body,type,parameters  *)
     attribute list
  | AInductiveDefinition of id *
     anninductiveType list *                         (* inductive types ,      *)