Skip to content

Commit

Permalink
Change datatype_kind to type_kind and type_kind to type_decl_kind
Browse files Browse the repository at this point in the history
  • Loading branch information
Nicolas Chataing committed May 3, 2021
1 parent bbda7c0 commit 3725284
Show file tree
Hide file tree
Showing 6 changed files with 11 additions and 11 deletions.
2 changes: 1 addition & 1 deletion typing/btype.ml
Original file line number Diff line number Diff line change
Expand Up @@ -349,7 +349,7 @@ type type_iterators =
it_functor_param: type_iterators -> functor_parameter -> unit;
it_module_type: type_iterators -> module_type -> unit;
it_class_type: type_iterators -> class_type -> unit;
it_type_kind: type_iterators -> type_kind -> unit;
it_type_kind: type_iterators -> type_decl_kind -> unit;
it_do_type_expr: type_iterators -> type_expr -> unit;
it_type_expr: type_iterators -> type_expr -> unit;
it_path: Path.t -> unit; }
Expand Down
4 changes: 2 additions & 2 deletions typing/btype.mli
Original file line number Diff line number Diff line change
Expand Up @@ -127,7 +127,7 @@ type type_iterators =
it_functor_param: type_iterators -> functor_parameter -> unit;
it_module_type: type_iterators -> module_type -> unit;
it_class_type: type_iterators -> class_type -> unit;
it_type_kind: type_iterators -> type_kind -> unit;
it_type_kind: type_iterators -> type_decl_kind -> unit;
it_do_type_expr: type_iterators -> type_expr -> unit;
it_type_expr: type_iterators -> type_expr -> unit;
it_path: Path.t -> unit; }
Expand Down Expand Up @@ -268,7 +268,7 @@ val set_commu: commutable ref -> commutable -> unit
(**** Forward declarations ****)
val print_raw: (Format.formatter -> type_expr -> unit) ref

val iter_type_expr_kind: (type_expr -> unit) -> (type_kind -> unit)
val iter_type_expr_kind: (type_expr -> unit) -> (type_decl_kind -> unit)

val iter_type_expr_cstr_args: (type_expr -> unit) ->
(constructor_arguments -> unit)
Expand Down
2 changes: 1 addition & 1 deletion typing/env.ml
Original file line number Diff line number Diff line change
Expand Up @@ -389,7 +389,7 @@ module IdTbl =
end

type type_descriptions =
(label_description, constructor_description) datatype_kind
(label_description, constructor_description) type_kind

let in_signature_flag = 0x01

Expand Down
2 changes: 1 addition & 1 deletion typing/env.mli
Original file line number Diff line number Diff line change
Expand Up @@ -59,7 +59,7 @@ val diff: t -> t -> Ident.t list
val copy_local: from:t -> t -> t

type type_descriptions =
(label_description, constructor_description) datatype_kind
(label_description, constructor_description) type_kind

(* For short-paths *)
type iter_cont
Expand Down
6 changes: 3 additions & 3 deletions typing/types.ml
Original file line number Diff line number Diff line change
Expand Up @@ -229,7 +229,7 @@ end
type type_declaration =
{ type_params: type_expr list;
type_arity: int;
type_kind: type_kind;
type_kind: type_decl_kind;
type_private: private_flag;
type_manifest: type_expr option;
type_variance: Variance.t list;
Expand All @@ -243,9 +243,9 @@ type type_declaration =
type_uid: Uid.t;
}

and type_kind = (label_declaration, constructor_declaration) datatype_kind
and type_decl_kind = (label_declaration, constructor_declaration) type_kind

and ('lbl, 'cstr) datatype_kind =
and ('lbl, 'cstr) type_kind =
Type_abstract
| Type_record of 'lbl list * record_representation
| Type_variant of 'cstr list
Expand Down
6 changes: 3 additions & 3 deletions typing/types.mli
Original file line number Diff line number Diff line change
Expand Up @@ -359,7 +359,7 @@ end
type type_declaration =
{ type_params: type_expr list;
type_arity: int;
type_kind: type_kind;
type_kind: type_decl_kind;
type_private: private_flag;
type_manifest: type_expr option;
type_variance: Variance.t list;
Expand All @@ -374,9 +374,9 @@ type type_declaration =
type_uid: Uid.t;
}

and type_kind = (label_declaration, constructor_declaration) datatype_kind
and type_decl_kind = (label_declaration, constructor_declaration) type_kind

and ('lbl, 'cstr) datatype_kind =
and ('lbl, 'cstr) type_kind =
Type_abstract
| Type_record of 'lbl list * record_representation
| Type_variant of 'cstr list
Expand Down

0 comments on commit 3725284

Please sign in to comment.