]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/cic_notation/cicNotationEnv.ml
ocaml 3.09 transition
[helm.git] / helm / ocaml / cic_notation / cicNotationEnv.ml
index f914b01d2ea57df51689ee1c5c76281dc8208cdb..62212f92fba871d7462d1b3ac80bb13d0574a193 100644 (file)
  * http://helm.cs.unibo.it/
  *)
 
-open CicNotationPt
+module Ast = CicNotationPt
 
 type value =
-  | TermValue of term
+  | TermValue of Ast.term
   | StringValue of string
   | NumValue of string
   | OptValue of value option
@@ -44,7 +44,7 @@ exception Type_mismatch of string * value_type
 
 type declaration = string * value_type
 type binding = string * (value_type * value)
-type t = (string * (value_type * value)) list
+type t = binding list
 
 let lookup env name =
   try
@@ -94,19 +94,19 @@ let opt_declaration (n, ty) = (n, OptType ty)
 let list_declaration (n, ty) = (n, ListType ty)
 
 let declaration_of_var = function
-  | NumVar s -> s, NumType
-  | IdentVar s -> s, StringType
-  | TermVar s -> s, TermType
+  | Ast.NumVar s -> s, NumType
+  | Ast.IdentVar s -> s, StringType
+  | Ast.TermVar s -> s, TermType
   | _ -> assert false
 
 let value_of_term = function
-  | Num (s, _) -> NumValue s
-  | Ident (s, None) -> StringValue s
+  | Ast.Num (s, _) -> NumValue s
+  | Ast.Ident (s, None) -> StringValue s
   | t -> TermValue t
 
 let term_of_value = function
-  | NumValue s -> Num (s, 0)
-  | StringValue s -> Ident (s, None)
+  | NumValue s -> Ast.Num (s, 0)
+  | StringValue s -> Ast.Ident (s, None)
   | TermValue t -> t
   | _ -> assert false (* TO BE UNDERSTOOD *)