Skip to content

Commit

Permalink
abstract row_field
Browse files Browse the repository at this point in the history
  • Loading branch information
t6s authored and garrigue committed Oct 21, 2021
1 parent 0684867 commit 2593bfd
Show file tree
Hide file tree
Showing 16 changed files with 307 additions and 205 deletions.
13 changes: 13 additions & 0 deletions Changes
Original file line number Diff line number Diff line change
Expand Up @@ -213,6 +213,12 @@ Working version
(Jacques Garrigue and Takafumi Saikawa,
review by Thomas Refis and Florian Angeletti)

* #10627: Make row_field abstract
Completes #10474 by making row_field abstract too.
An immutable view row_field_view is provided, and one converts between it
and row_field via inj_row_field and row_field_repr.
(Jacques Garrigue and Takafumi Saikawa, review by Florian Angeletti)

- #10433: Remove the distinction between 32-bit aligned and 64-bit aligned
64-bit floats in Cmm.memory_chunk.
(Greta Yorsh, review by Xavier Leroy)
Expand Down Expand Up @@ -755,6 +761,13 @@ OCaml 4.13.0 (24 September 2021)
- #10327: Add a subdirectories variable and a copy action to ocamltest
(Sébastien Hinderer, review by David Allsopp)

* #10337: Normalize type_expr nodes on access
One should now use accessors such as get_desc and get_level to access fields
of type_expr, rather than calling manually Btype.repr (which is now hidden
in Types.Transient_expr).
(Jacques Garrigue and Takafumi Saikawa,
review by Florian Angeletti and Gabriel Radanne)

- #10358: Use a hash table for the load path.
(Leo White, review by Gabriel Scherer)

Expand Down
Binary file modified boot/ocamlc
Binary file not shown.
4 changes: 2 additions & 2 deletions lambda/matching.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1807,7 +1807,7 @@ let divide_variant ~scopes row ctx { cases = cl; args; default = def } =
in
let head = Simple.head p in
let variants = divide rem in
if row_field lab row = Rabsent then
if row_field_repr (get_row_field lab row) = Rabsent then
variants
else
let tag = Btype.hash_variant lab in
Expand Down Expand Up @@ -2908,7 +2908,7 @@ let combine_variant loc row arg partial ctx def (tag_lambda_list, total1, _pats)
(fun (_, f) ->
match row_field_repr f with
| Rabsent
| Reither (true, _ :: _, _, _) ->
| Reither (true, _ :: _, _) ->
()
| _ -> incr num_constr)
(row_fields row)
Expand Down
2 changes: 1 addition & 1 deletion toplevel/genprintval.ml
Original file line number Diff line number Diff line change
Expand Up @@ -452,7 +452,7 @@ module Make(O : OBJ)(EVP : EVALPATH with type valu = O.t) = struct
| (l, f) :: fields ->
if Btype.hash_variant l = tag then
match row_field_repr f with
| Rpresent(Some ty) | Reither(_,[ty],_,_) ->
| Rpresent(Some ty) | Reither(_,[ty],_) ->
let args =
nest tree_of_val (depth - 1) (O.field obj 1) ty
in
Expand Down
12 changes: 6 additions & 6 deletions typing/btype.ml
Original file line number Diff line number Diff line change
Expand Up @@ -240,7 +240,7 @@ let fold_row f init row =
(fun init (_, fi) ->
match row_field_repr fi with
| Rpresent(Some ty) -> f init ty
| Reither(_, tl, _, _) -> List.fold_left f init tl
| Reither(_, tl, _) -> List.fold_left f init tl
| _ -> init)
init
(row_fields row)
Expand Down Expand Up @@ -420,13 +420,13 @@ let copy_row f fixed row keep more =
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
| Rpresent oty -> rf_present (Option.map f oty)
| Reither(c, tl, m) ->
let use_ext_of = if keep then Some fi else None in
let m = if is_fixed row then fixed else m in
let tl = List.map f tl in
Reither(c, tl, m, e)
| _ -> fi)
rf_either tl ?use_ext_of ~no_arg:c ~matched:m
| Rabsent -> rf_absent)
orig_fields in
let name =
match orig_name with
Expand Down

0 comments on commit 2593bfd

Please sign in to comment.