Skip to content

Commit 405ec2a

Browse files
committed
Create tagged switch scrutinee while going down
1 parent 4a714a9 commit 405ec2a

File tree

3 files changed

+88
-6
lines changed

3 files changed

+88
-6
lines changed

middle_end/flambda/simplify/simplify_expr.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -37,6 +37,7 @@ let rec simplify_expr dacc expr ~down_to_up =
3737
Simplify_apply_cont_expr.simplify_apply_cont dacc apply_cont ~down_to_up
3838
| Switch switch ->
3939
Simplify_switch_expr.simplify_switch ~simplify_let dacc switch ~down_to_up
40+
~original_expr:expr
4041
| Invalid _ ->
4142
(* CR mshinwell: Make sure that a program can be simplified to just
4243
[Invalid]. [Un_cps] should translate any [Invalid] that it sees as if

middle_end/flambda/simplify/simplify_switch_expr.ml

Lines changed: 86 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -258,13 +258,14 @@ let rebuild_switch ~simplify_let dacc ~arms ~scrutinee ~scrutinee_ty uacc
258258
in
259259
after_rebuild expr uacc
260260

261-
let simplify_switch ~simplify_let dacc switch ~down_to_up =
261+
let simplify_switch_aux ~simplify_let
262+
~scrutinee ~scrutinee_ty
263+
~tagged_scrutinee:_ ~not_scrutinee:_
264+
dacc switch
265+
~(down_to_up:
266+
(Rebuilt_expr.t * Upwards_acc.t,
267+
Rebuilt_expr.t * Upwards_acc.t) Simplify_common.down_to_up) =
262268
let module AC = Apply_cont in
263-
let scrutinee = Switch.scrutinee switch in
264-
let scrutinee_ty =
265-
S.simplify_simple dacc scrutinee ~min_name_mode:NM.normal
266-
in
267-
let scrutinee = T.get_alias_exn scrutinee_ty in
268269
let arms, dacc =
269270
let typing_env_at_use = DA.typing_env dacc in
270271
Target_imm.Map.fold (fun arm action (arms, dacc) ->
@@ -308,3 +309,82 @@ let simplify_switch ~simplify_let dacc switch ~down_to_up =
308309
down_to_up dacc
309310
~rebuild:(rebuild_switch ~simplify_let dacc ~arms ~scrutinee
310311
~scrutinee_ty)
312+
313+
let simplify_switch
314+
~(simplify_let:Flambda.Let.t Simplify_common.expr_simplifier)
315+
~original_expr
316+
dacc switch
317+
~(down_to_up:
318+
(Rebuilt_expr.t * Upwards_acc.t,
319+
Rebuilt_expr.t * Upwards_acc.t) Simplify_common.down_to_up) =
320+
let scrutinee = Switch.scrutinee switch in
321+
let scrutinee_ty =
322+
S.simplify_simple dacc scrutinee ~min_name_mode:NM.normal
323+
in
324+
let scrutinee = T.get_alias_exn scrutinee_ty in
325+
let find_cse_simple prim =
326+
let with_fixed_value = P.Eligible_for_cse.create_exn prim in
327+
match DE.find_cse (DA.denv dacc) with_fixed_value with
328+
| None -> None
329+
| Some simple ->
330+
match
331+
TE.get_canonical_simple_exn (DA.typing_env dacc) simple
332+
~min_name_mode:NM.normal
333+
~name_mode_of_existing_simple:NM.normal
334+
with
335+
| exception Not_found -> None
336+
| simple -> Some simple
337+
in
338+
let create_def name prim =
339+
let bound_to = Variable.create name in
340+
let bound_to = Var_in_binding_pos.create bound_to NM.normal in
341+
let defining_expr = Named.create_prim prim Debuginfo.none in
342+
let let_expr =
343+
Let.create (Bindable_let_bound.singleton bound_to)
344+
defining_expr
345+
~body:original_expr
346+
~free_names_of_body:Unknown
347+
in
348+
simplify_let dacc let_expr ~down_to_up
349+
in
350+
let tag_prim = P.Unary (Box_number Untagged_immediate, scrutinee) in
351+
Simple.pattern_match scrutinee
352+
~const:(fun const ->
353+
match Reg_width_things.Const.descr const with
354+
| Naked_immediate imm ->
355+
let tagged_scrutinee =
356+
Simple.const (Reg_width_things.Const.tagged_immediate imm)
357+
in
358+
let not_scrutinee =
359+
let not_imm =
360+
if Target_imm.equal imm Target_imm.zero then
361+
Target_imm.one
362+
else
363+
(* If the scrutinee is neither zero nor one, this value
364+
won't be used *)
365+
Target_imm.zero
366+
in
367+
Simple.const (Reg_width_things.Const.tagged_immediate not_imm)
368+
in
369+
simplify_switch_aux dacc switch ~down_to_up
370+
~tagged_scrutinee ~not_scrutinee
371+
~scrutinee ~scrutinee_ty
372+
~simplify_let
373+
| Tagged_immediate _ | Naked_float _ | Naked_int32 _
374+
| Naked_int64 _ | Naked_nativeint _ ->
375+
Misc.fatal_errorf "Switch scrutinee is not a naked immediate: %a"
376+
Simple.print scrutinee)
377+
~name:(fun _ ->
378+
match find_cse_simple tag_prim with
379+
| None ->
380+
create_def "tagged_scrutinee" tag_prim
381+
| Some tagged_scrutinee ->
382+
let not_prim = P.Unary (Boolean_not, tagged_scrutinee) in
383+
match find_cse_simple not_prim with
384+
| None ->
385+
create_def "not_scrutinee" not_prim
386+
| Some not_scrutinee ->
387+
simplify_switch_aux dacc switch ~down_to_up
388+
~tagged_scrutinee ~not_scrutinee
389+
~simplify_let
390+
~scrutinee ~scrutinee_ty)

middle_end/flambda/simplify/simplify_switch_expr.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -18,4 +18,5 @@
1818

1919
val simplify_switch
2020
: simplify_let:Flambda.Let.t Simplify_common.expr_simplifier
21+
-> original_expr:Flambda.Expr.t
2122
-> Flambda.Switch.t Simplify_common.expr_simplifier

0 commit comments

Comments
 (0)