Skip to content

Commit

Permalink
remove the dummy field row_bound
Browse files Browse the repository at this point in the history
  • Loading branch information
t6s committed Jun 23, 2021
1 parent 4840834 commit 1c087cc
Show file tree
Hide file tree
Showing 3 changed files with 1 addition and 5 deletions.
Binary file modified boot/ocamlc
Binary file not shown.
Binary file modified boot/ocamllex
Binary file not shown.
6 changes: 1 addition & 5 deletions typing/types.ml
Expand Up @@ -45,7 +45,6 @@ and type_desc =
and row_desc =
{ row_fields: (label * row_field) list;
row_more: type_expr;
row_bound: unit;
row_closed: bool;
row_fixed: fixed_explanation option;
row_name: (Path.t * type_expr list) option }
Expand Down Expand Up @@ -563,7 +562,7 @@ let compare_type t1 t2 = compare (get_id t1) (get_id t2)
(* Constructor and accessors for [row_desc] *)

let create_row ~fields ~more ~closed ~fixed ~name =
{ row_fields=fields; row_more=more; row_bound=();
{ row_fields=fields; row_more=more;
row_closed=closed; row_fixed=fixed; row_name=name }

let rec rev_concat l ll =
Expand Down Expand Up @@ -614,9 +613,6 @@ let row_repr row =
fixed = row.row_fixed;
name = row.row_name }

(* just to avoid the "unused constructor" warning.. *)
let _row_bound row = row.row_bound

let rec row_field_repr_aux tl = function
Reither(_, tl', _, {contents = Some fi}) ->
row_field_repr_aux (tl@tl') fi
Expand Down

0 comments on commit 1c087cc

Please sign in to comment.