we must forget abbrevs when switching to the old method of unification. removed unify_old: unify now decides for itself whether to use the old or the new method
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/gadts@10803 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
674cd74009
commit
ac4fa5ae13
|
@ -2015,7 +2015,9 @@ and unify3 mode env t1 t1' t2 t2' =
|
|||
in
|
||||
let switch_to_old_link () =
|
||||
match mode with
|
||||
| Pattern | Expression -> old_link ();
|
||||
| Pattern | Expression ->
|
||||
cleanup_abbrev ();
|
||||
old_link ();
|
||||
| Old -> () (* old_link was already called *)
|
||||
in
|
||||
match d1, d2 with
|
||||
|
@ -2391,13 +2393,12 @@ let unify_pairs env ty1 ty2 pairs =
|
|||
univar_pairs := pairs;
|
||||
unify Expression env ty1 ty2
|
||||
|
||||
let unify_old env ty1 ty2 =
|
||||
univar_pairs := [];
|
||||
unify Old (ref env) ty1 ty2
|
||||
|
||||
let unify env ty1 ty2 =
|
||||
univar_pairs := [];
|
||||
unify Expression (ref env) ty1 ty2
|
||||
if Env.has_local_constraints env then
|
||||
unify Expression (ref env) ty1 ty2
|
||||
else
|
||||
unify Old (ref env) ty1 ty2
|
||||
|
||||
let unify_gadt env ty1 ty2 =
|
||||
univar_pairs := [];
|
||||
|
|
|
@ -141,8 +141,6 @@ val full_expand: Env.t -> type_expr -> type_expr
|
|||
|
||||
val enforce_constraints: Env.t -> type_expr -> unit
|
||||
|
||||
val unify_old: Env.t -> type_expr -> type_expr -> unit
|
||||
(* Unify the two types given. Raise [Unify] if not possible. Use the old method of unification *)
|
||||
val unify: Env.t -> type_expr -> type_expr -> unit
|
||||
(* Unify the two types given. Raise [Unify] if not possible. *)
|
||||
val unify_gadt: int -> Env.t ref -> type_expr -> type_expr -> unit
|
||||
|
|
|
@ -165,10 +165,7 @@ let unify_exp_types loc env ty expected_ty =
|
|||
(* Format.eprintf "@[%a@ %a@]@." Printtyp.raw_type_expr exp.exp_type
|
||||
Printtyp.raw_type_expr expected_ty; *)
|
||||
try
|
||||
if Env.has_local_constraints env then
|
||||
unify env ty expected_ty
|
||||
else
|
||||
unify_old env ty expected_ty
|
||||
unify env ty expected_ty
|
||||
with
|
||||
Unify trace ->
|
||||
raise(Error(loc, Expr_type_clash(trace)))
|
||||
|
|
Loading…
Reference in New Issue