1818
1919open ! Simplify_import
2020
21- let rebuild_switch ~simplify_let : _ _dacc ~ arms ~scrutinee ~scrutinee_ty
21+ let rebuild_switch ~arms ~scrutinee ~scrutinee_ty
2222 ~tagged_scrutinee ~not_scrutinee uacc ~after_rebuild =
2323 let new_let_conts, arms, identity_arms, not_arms =
2424 Target_imm.Map. fold
@@ -218,13 +218,9 @@ let rebuild_switch ~simplify_let:_ _dacc ~arms ~scrutinee ~scrutinee_ty
218218 in
219219 after_rebuild expr uacc
220220
221- let simplify_switch_aux ~simplify_let
222- ~scrutinee ~scrutinee_ty
221+ let simplify_switch_aux ~scrutinee ~scrutinee_ty
223222 ~tagged_scrutinee ~not_scrutinee
224- dacc switch
225- ~(down_to_up :
226- (Rebuilt_expr.t * Upwards_acc.t,
227- Rebuilt_expr.t * Upwards_acc.t) Simplify_common.down_to_up ) =
223+ dacc switch ~down_to_up =
228224 let module AC = Apply_cont in
229225 let arms, dacc =
230226 let typing_env_at_use = DA. typing_env dacc in
@@ -267,22 +263,17 @@ let simplify_switch_aux ~simplify_let
267263 (Target_imm.Map. empty, dacc)
268264 in
269265 down_to_up dacc
270- ~rebuild: (rebuild_switch ~simplify_let dacc ~ arms ~scrutinee
266+ ~rebuild: (rebuild_switch ~arms ~scrutinee
271267 ~scrutinee_ty ~tagged_scrutinee ~not_scrutinee )
272268
273- let simplify_switch
274- ~(simplify_let :Flambda.Let.t Simplify_common.expr_simplifier )
275- ~original_expr
276- dacc switch
277- ~(down_to_up :
278- (Rebuilt_expr.t * Upwards_acc.t,
279- Rebuilt_expr.t * Upwards_acc.t) Simplify_common.down_to_up ) =
269+ let simplify_switch ~simplify_let ~original_expr dacc switch ~down_to_up =
280270 let scrutinee = Switch. scrutinee switch in
281271 let scrutinee_ty =
282272 S. simplify_simple dacc scrutinee ~min_name_mode: NM. normal
283273 in
284274 let scrutinee = T. get_alias_exn scrutinee_ty in
285275 let find_cse_simple prim =
276+ (* prim is either boolean not or tagging of non constant values *)
286277 let with_fixed_value = P.Eligible_for_cse. create_exn prim in
287278 match DE. find_cse (DA. denv dacc) with_fixed_value with
288279 | None -> None
@@ -330,7 +321,6 @@ let simplify_switch
330321 simplify_switch_aux dacc switch ~down_to_up
331322 ~tagged_scrutinee ~not_scrutinee
332323 ~scrutinee ~scrutinee_ty
333- ~simplify_let
334324 | Tagged_immediate _ | Naked_float _ | Naked_int32 _
335325 | Naked_int64 _ | Naked_nativeint _ ->
336326 Misc. fatal_errorf " Switch scrutinee is not a naked immediate: %a"
@@ -347,5 +337,4 @@ let simplify_switch
347337 | Some not_scrutinee ->
348338 simplify_switch_aux dacc switch ~down_to_up
349339 ~tagged_scrutinee ~not_scrutinee
350- ~simplify_let
351340 ~scrutinee ~scrutinee_ty )
0 commit comments