environment local constraint marker

git-svn-id: http://caml.inria.fr/svn/ocaml/branches/gadts@10754 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Jacques Le Normand 2010-11-01 05:09:36 +00:00
parent ec375d6e40
commit 6f151a0f95
3 changed files with 8 additions and 3 deletions

View File

@ -1619,7 +1619,7 @@ let reify env t =
let name = get_new_abstract_name () in
if row then name ^ "#row" else name
in
let (id, new_env) = Env.enter_type name decl !env in
let (id, new_env) = Env.enter_local_constraint name decl !env in
let t = newty2 pattern_level (Tconstr (Path.Pident id,[],ref Mnil)) in
env := new_env;
t

View File

@ -53,7 +53,8 @@ type t = {
components: (Path.t * module_components) Ident.tbl;
classes: (Path.t * class_declaration) Ident.tbl;
cltypes: (Path.t * cltype_declaration) Ident.tbl;
summary: summary
summary: summary;
local_constraints: bool;
}
and module_components = module_components_repr Lazy.t
@ -93,7 +94,7 @@ let empty = {
modules = Ident.empty; modtypes = Ident.empty;
components = Ident.empty; classes = Ident.empty;
cltypes = Ident.empty; constrs_by_type = Ident.empty ;
summary = Env_empty }
summary = Env_empty; local_constraints = false; }
let diff_keys is_local tbl1 tbl2 =
let keys2 = Ident.keys tbl2 in
@ -742,6 +743,9 @@ and enter_modtype = enter store_modtype
and enter_class = enter store_class
and enter_cltype = enter store_cltype
let enter_local_constraint x y z =
let (ident,env) = enter_type x y z in
(ident, { env with local_constraints = true })
(* Insertion of all components of a signature *)
let add_item comp env =

View File

@ -80,6 +80,7 @@ val open_pers_signature: string -> t -> t
val enter_value: string -> value_description -> t -> Ident.t * t
val enter_type: string -> type_declaration -> t -> Ident.t * t
val enter_local_constraint: string -> type_declaration -> t -> Ident.t * t
val enter_exception: string -> exception_declaration -> t -> Ident.t * t
val enter_module: string -> module_type -> t -> Ident.t * t
val enter_modtype: string -> modtype_declaration -> t -> Ident.t * t