1995-08-09 08:06:35 -07:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Objective Caml *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* Automatique. Distributed only by permission. *)
|
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(* $Id$ *)
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
(* Inclusion checks for the core language *)
|
|
|
|
|
|
|
|
open Misc
|
|
|
|
open Path
|
1996-09-23 04:33:27 -07:00
|
|
|
open Types
|
1995-05-04 03:15:53 -07:00
|
|
|
open Typedtree
|
|
|
|
|
1995-05-05 03:05:18 -07:00
|
|
|
(* Inclusion between value descriptions *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1995-10-23 09:59:41 -07:00
|
|
|
exception Dont_match
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
let value_descriptions env vd1 vd2 =
|
1995-10-23 09:59:41 -07:00
|
|
|
if Ctype.moregeneral env vd1.val_type vd2.val_type then begin
|
1996-04-22 04:15:41 -07:00
|
|
|
match (vd1.val_kind, vd2.val_kind) with
|
|
|
|
(Val_prim p1, Val_prim p2) ->
|
1995-10-23 09:59:41 -07:00
|
|
|
if p1 = p2 then Tcoerce_none else raise Dont_match
|
1996-04-22 04:15:41 -07:00
|
|
|
| (Val_prim p, _) -> Tcoerce_primitive p
|
|
|
|
| (_, Val_prim p) -> raise Dont_match
|
|
|
|
| (_, _) -> Tcoerce_none
|
1995-10-23 09:59:41 -07:00
|
|
|
end else
|
|
|
|
raise Dont_match
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* Inclusion between type declarations *)
|
|
|
|
|
|
|
|
let type_declarations env id decl1 decl2 =
|
|
|
|
decl1.type_arity = decl2.type_arity &
|
|
|
|
begin match (decl1.type_kind, decl2.type_kind) with
|
1995-09-26 13:23:29 -07:00
|
|
|
(_, Type_abstract) -> true
|
1995-05-04 03:15:53 -07:00
|
|
|
| (Type_variant cstrs1, Type_variant cstrs2) ->
|
|
|
|
for_all2
|
|
|
|
(fun (cstr1, arg1) (cstr2, arg2) ->
|
|
|
|
cstr1 = cstr2 &
|
|
|
|
for_all2
|
|
|
|
(fun ty1 ty2 ->
|
1997-02-20 12:39:02 -08:00
|
|
|
Ctype.equal env true (ty1::decl1.type_params)
|
|
|
|
(ty2::decl2.type_params))
|
1995-05-04 03:15:53 -07:00
|
|
|
arg1 arg2)
|
|
|
|
cstrs1 cstrs2
|
|
|
|
| (Type_record labels1, Type_record labels2) ->
|
|
|
|
for_all2
|
|
|
|
(fun (lbl1, mut1, ty1) (lbl2, mut2, ty2) ->
|
|
|
|
lbl1 = lbl2 & mut1 = mut2 &
|
1997-02-20 12:39:02 -08:00
|
|
|
Ctype.equal env true (ty1::decl1.type_params)
|
|
|
|
(ty2::decl2.type_params))
|
1995-05-04 03:15:53 -07:00
|
|
|
labels1 labels2
|
1995-09-26 13:23:29 -07:00
|
|
|
| (_, _) -> false
|
|
|
|
end &
|
|
|
|
begin match (decl1.type_manifest, decl2.type_manifest) with
|
1997-02-20 12:39:02 -08:00
|
|
|
(_, None) ->
|
|
|
|
Ctype.equal env true decl1.type_params decl2.type_params
|
1995-09-26 13:23:29 -07:00
|
|
|
| (Some ty1, Some ty2) ->
|
1997-02-20 12:39:02 -08:00
|
|
|
Ctype.equal env true (ty1::decl1.type_params)
|
|
|
|
(ty2::decl2.type_params)
|
1995-09-26 13:23:29 -07:00
|
|
|
| (None, Some ty2) ->
|
1996-04-22 04:15:41 -07:00
|
|
|
let ty1 =
|
1997-03-24 12:11:22 -08:00
|
|
|
Btype.newgenty (Tconstr(Pident id, decl2.type_params, ref Mnil))
|
|
|
|
in
|
|
|
|
Ctype.equal env true decl1.type_params decl2.type_params
|
|
|
|
&
|
|
|
|
Ctype.equal env false [ty1] [ty2]
|
1995-05-04 03:15:53 -07:00
|
|
|
end
|
|
|
|
|
|
|
|
(* Inclusion between exception declarations *)
|
|
|
|
|
|
|
|
let exception_declarations env ed1 ed2 =
|
1997-02-20 12:39:02 -08:00
|
|
|
for_all2 (fun ty1 ty2 -> Ctype.equal env false [ty1] [ty2]) ed1 ed2
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1996-04-22 04:15:41 -07:00
|
|
|
(* Inclusion between class types *)
|
1996-05-14 08:38:36 -07:00
|
|
|
let encode_val (mut, ty) rem =
|
|
|
|
begin match mut with
|
|
|
|
Asttypes.Mutable -> Predef.type_unit
|
|
|
|
| Asttypes.Immutable -> Ctype.newgenty Tvar
|
|
|
|
end
|
|
|
|
::ty::rem
|
|
|
|
|
|
|
|
let vars vars1 vars2 =
|
|
|
|
Vars.fold
|
|
|
|
(fun lab v2 (vl1, vl2) ->
|
|
|
|
(begin try
|
|
|
|
encode_val (Vars.find lab vars1) vl1
|
|
|
|
with Not_found ->
|
|
|
|
vl1
|
|
|
|
end,
|
|
|
|
encode_val v2 vl2))
|
|
|
|
vars2 ([], [])
|
1996-04-22 04:15:41 -07:00
|
|
|
|
1997-03-09 16:23:13 -08:00
|
|
|
let class_types env d1 d2 =
|
1996-04-22 04:15:41 -07:00
|
|
|
(* Same abbreviations *)
|
1997-02-20 12:39:02 -08:00
|
|
|
Ctype.equal env true
|
|
|
|
(d1.cty_self::d1.cty_params) (d2.cty_self::d2.cty_params)
|
|
|
|
&&
|
1996-04-22 04:15:41 -07:00
|
|
|
(* Same concretes methods *)
|
1996-06-03 09:26:27 -07:00
|
|
|
Concr.equal d1.cty_concr d2.cty_concr
|
1997-02-20 12:39:02 -08:00
|
|
|
&&
|
1996-04-22 04:15:41 -07:00
|
|
|
(* If virtual, stays virtual *)
|
|
|
|
(d1.cty_new <> None or d2.cty_new = None)
|
1997-02-20 12:39:02 -08:00
|
|
|
&&
|
1996-04-22 04:15:41 -07:00
|
|
|
(* Less general *)
|
1996-05-14 08:38:36 -07:00
|
|
|
let (v1, v2) = vars d1.cty_vars d2.cty_vars in
|
|
|
|
let t1 = Ctype.newgenty (Ttuple (d1.cty_self::v1@d1.cty_args)) in
|
|
|
|
let t2 = Ctype.newgenty (Ttuple (d2.cty_self::v2@d2.cty_args)) in
|
1996-04-22 04:15:41 -07:00
|
|
|
Ctype.moregeneral env t1 t2
|