forget row_bound
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@4593 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
06db32f483
commit
a35fbd9077
|
@ -142,20 +142,25 @@ let iter_type_expr f ty =
|
|||
| Tsubst ty -> f ty
|
||||
|
||||
let copy_row f row keep more =
|
||||
let bound = ref [] in
|
||||
let fields = List.map
|
||||
(fun (l, fi) -> l,
|
||||
match row_field_repr fi with
|
||||
| Rpresent(Some ty) -> Rpresent(Some(f ty))
|
||||
| Reither(c, tl, m, e) ->
|
||||
let e = if keep then e else ref None in
|
||||
Reither(c, List.map f tl, m, e)
|
||||
let tl = List.map f tl in
|
||||
bound := List.filter
|
||||
(function {desc=Tconstr(_,[],_)} -> false | _ -> true)
|
||||
(List.map repr tl)
|
||||
@ !bound;
|
||||
Reither(c, tl, m, e)
|
||||
| _ -> fi)
|
||||
row.row_fields in
|
||||
let name =
|
||||
match row.row_name with None -> None
|
||||
| Some (path, tl) -> Some (path, List.map f tl) in
|
||||
{ row_fields = fields; row_more = more;
|
||||
row_bound = List.map f row.row_bound;
|
||||
{ row_fields = fields; row_more = more; row_bound = !bound;
|
||||
row_closed = row.row_closed; row_name = name; }
|
||||
|
||||
let rec copy_kind = function
|
||||
|
|
|
@ -106,11 +106,12 @@ let rec typexp s ty =
|
|||
save_desc more more.desc;
|
||||
more.desc <- ty.desc;
|
||||
let more' =
|
||||
if static then
|
||||
if s.for_saving then newpersvar () else newgenvar ()
|
||||
else more in
|
||||
if s.for_saving then newpersvar () else
|
||||
if static then newgenvar () else more in
|
||||
(* Return a new copy *)
|
||||
let row = copy_row (typexp s) row true more' in
|
||||
let row = copy_row (typexp s) row (not s.for_saving) more' in
|
||||
let row =
|
||||
if s.for_saving then {row with row_bound = []} else row in
|
||||
match row.row_name with
|
||||
Some (p, tl) ->
|
||||
Tvariant {row with row_name = Some (type_path s p, tl)}
|
||||
|
|
Loading…
Reference in New Issue