Skip to content

Commit

Permalink
unroll repr_link once for a small peformance gain
Browse files Browse the repository at this point in the history
  • Loading branch information
garrigue committed Apr 13, 2021
1 parent f82c1eb commit fe13341
Showing 1 changed file with 16 additions and 10 deletions.
26 changes: 16 additions & 10 deletions typing/types.ml
Original file line number Diff line number Diff line change
Expand Up @@ -514,24 +514,30 @@ let rec field_kind_repr =
Fvar {contents = Some kind} -> field_kind_repr kind
| kind -> kind

let rec repr_link compress (t : type_expr) d : type_expr -> type_expr =
let rec repr_link (t : type_expr) d : type_expr -> type_expr =
function
{desc = Tlink t' as d'} ->
repr_link true t d' t'
repr_link t d' t'
| {desc = Tfield (_, k, _, t') as d'} when field_kind_repr k = Fabsent ->
repr_link true t d' t'
repr_link t d' t'
| t' ->
if compress then begin
log_change (Ccompress (t, t.desc, d)); t.desc <- d
end;
log_change (Ccompress (t, t.desc, d));
t.desc <- d;
t'

let repr_link1 t = function
{desc = Tlink t' as d'} ->
repr_link t d' t'
| {desc = Tfield (_, k, _, t') as d'} when field_kind_repr k = Fabsent ->
repr_link t d' t'
| t' -> t'

let repr t =
match t.desc with
Tlink t' as d ->
repr_link false t d t'
| Tfield (_, k, _, t') as d when field_kind_repr k = Fabsent ->
repr_link false t d t'
Tlink t' ->
repr_link1 t t'
| Tfield (_, k, _, t') when field_kind_repr k = Fabsent ->
repr_link1 t t'
| _ -> t

(* getters for type_expr *)
Expand Down

0 comments on commit fe13341

Please sign in to comment.