Skip to content

Commit

Permalink
Review: Comment + cleanup in matching.ml
Browse files Browse the repository at this point in the history
  • Loading branch information
lthls committed Oct 20, 2021
1 parent 8a143f4 commit 39ca4ca
Showing 1 changed file with 9 additions and 5 deletions.
14 changes: 9 additions & 5 deletions lambda/matching.ml
Original file line number Diff line number Diff line change
Expand Up @@ -2835,11 +2835,15 @@ let combine_constructor loc arg pat_env cstr partial ctx def
match
(cstr.cstr_consts, cstr.cstr_nonconsts, consts, nonconsts)
with
| 1, 1, [ (0, act1) ], [ (0, act2) ]
when not !Clflags.native_code ->
(* Typically, match on lists, will avoid isint primitive in that
case *)
Lifthenelse (arg, act2, act1)
| 1, 1, [ (0, act1) ], [ (0, act2) ] ->
if !Clflags.native_code then
Lifthenelse(Lprim (Pisint, [ arg ], loc), act1, act2)
else
(* PR#10681: we use [arg] directly as the test here;
it generates better bytecode for this common case
(typically options and lists), but would prevent
some optimizations with the native compiler. *)
Lifthenelse (arg, act2, act1)
| n, 0, _, [] ->
(* The type defines constant constructors only *)
call_switcher loc fail_opt arg 0 (n - 1) consts
Expand Down

0 comments on commit 39ca4ca

Please sign in to comment.