]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/cic_notation/cicNotationPt.ml
ocaml 3.09 transition
[helm.git] / helm / ocaml / cic_notation / cicNotationPt.ml
index ca00d35396771622d890785a69dd9425d71893c6..ac6a0edbd1a37a9e1684a4089b9fd8849a3e3342 100644 (file)
@@ -27,7 +27,7 @@
 
 type binder_kind = [ `Lambda | `Pi | `Exists | `Forall ]
 type induction_kind = [ `Inductive | `CoInductive ]
-type sort_kind = [ `Prop | `Set | `Type | `CProp ]
+type sort_kind = [ `Prop | `Set | `Type of CicUniv.universe | `CProp ]
 type fold_kind = [ `Left | `Right ]
 
 type location = Lexing.position * Lexing.position
@@ -41,11 +41,13 @@ let fail floc msg =
 
 type href = UriManager.uri
 
+type child_pos = [ `Left | `Right | `Inner ]
+
 type term_attribute =
   [ `Loc of location                  (* source file location *)
   | `IdRef of string                  (* ACic pointer *)
-  | `Href of href list                (* hyperlinks for literals *)
   | `Level of int * Gramext.g_assoc   (* precedence, associativity *)
+  | `ChildPos of child_pos            (* position of l1 pattern variables *)
   | `XmlAttrs of (string option * string * string) list
       (* list of XML attributes: namespace, name, value *)
   | `Raw of string                    (* unparsed version *)
@@ -59,6 +61,10 @@ type literal =
 
 type case_indtype = string * href option
 
+(** To be increased each time the term type below changes, used for "safe"
+ * marshalling *)
+let magic = 1
+
 type term =
   (* CIC AST *)