Skip to content

Commit

Permalink
fix: merge the right fixity information
Browse files Browse the repository at this point in the history
  • Loading branch information
Octachron committed Jul 12, 2019
1 parent e77d0b0 commit a8bbb60
Show file tree
Hide file tree
Showing 3 changed files with 10 additions and 5 deletions.
6 changes: 3 additions & 3 deletions typing/btype.ml
Original file line number Diff line number Diff line change
Expand Up @@ -167,8 +167,8 @@ let rec row_more row =
| {desc=Tvariant row'} -> row_more row'
| ty -> ty

let merge_fixed_explanation row1 row2 =
match row1.row_fixed, row2.row_fixed with
let merge_fixed_explanation fixed1 fixed2 =
match fixed1, fixed2 with
| Some Univar _ as x, _ | _, (Some Univar _ as x) -> x
| Some Fixed_private as x, _ | _, (Some Fixed_private as x) -> x
| Some Reified _ as x, _ | _, (Some Reified _ as x) -> x
Expand Down Expand Up @@ -447,7 +447,7 @@ let copy_row f fixed row keep more =
| Rpresent(Some ty) -> Rpresent(Some(f ty))
| Reither(c, tl, m, e) ->
let e = if keep then e else ref None in
let m = if row.row_fixed <> None then fixed else m 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)
Expand Down
7 changes: 6 additions & 1 deletion typing/btype.mli
Original file line number Diff line number Diff line change
Expand Up @@ -72,13 +72,18 @@ val row_more: row_desc -> type_expr

val is_fixed: row_desc -> bool
(* Return whether the row is directly marked as fixed or not *)

val row_fixed: row_desc -> bool
(* Return whether the row should be treated as fixed or not.
In particular, [is_fixed row] implies [row_fixed row].
*)

val fixed_explanation: row_desc -> fixed_explanation option
(* Return the potential explanation for the fixed row *)
val merge_fixed_explanation: row_desc -> row_desc -> fixed_explanation option

val merge_fixed_explanation:
fixed_explanation option -> fixed_explanation option
-> fixed_explanation option
(* Merge two explanations for a fixed row *)

val static_row: row_desc -> bool
Expand Down
2 changes: 1 addition & 1 deletion typing/ctype.ml
Original file line number Diff line number Diff line change
Expand Up @@ -2815,7 +2815,7 @@ and unify_row env row1 row2 =
| None, Some _ -> rm2
| None, None -> newty2 (min rm1.level rm2.level) (Tvar None)
in
let fixed = merge_fixed_explanation row1 row2
let fixed = merge_fixed_explanation fixed1 fixed2
and closed = row1.row_closed || row2.row_closed in
let keep switch =
List.for_all
Expand Down

0 comments on commit a8bbb60

Please sign in to comment.