@@ -106,7 +106,7 @@ module type S =
106106 val make_isout : act -> act -> act
107107 val make_isin : act -> act -> act
108108 val make_if : act -> act -> act -> act
109- val make_switch : Location .t -> act -> int array -> act array -> Lambda .switch_names option -> act
109+ val make_switch : Location .t -> act -> int array -> act array -> offset : int -> Lambda .switch_names option -> act
110110 val make_catch : act -> int * (act -> act )
111111 val make_exit : int -> act
112112 end
@@ -560,6 +560,9 @@ and enum top cases =
560560 do_make_if_out
561561 (Arg. make_const d) ctx.arg (mk_ifso ctx) (mk_ifno ctx)
562562 | _ ->
563+ if (* true || *) ! Config. bs_only then
564+ do_make_if_out
565+ (Arg. make_const d) (Arg. make_offset ctx.arg (- l)) (mk_ifso ctx) (mk_ifno ctx) else
563566 Arg. bind
564567 (Arg. make_offset ctx.arg (- l))
565568 (fun arg ->
@@ -575,6 +578,9 @@ and enum top cases =
575578 do_make_if_in
576579 (Arg. make_const d) ctx.arg (mk_ifso ctx) (mk_ifno ctx)
577580 | _ ->
581+ if (* true || *) ! Config. bs_only then
582+ do_make_if_in
583+ (Arg. make_const d) (Arg. make_offset ctx.arg (- l)) (mk_ifso ctx) (mk_ifno ctx) else
578584 Arg. bind
579585 (Arg. make_offset ctx.arg (- l))
580586 (fun arg ->
@@ -750,12 +756,15 @@ let make_switch loc {cases=cases ; actions=actions} i j sw_names =
750756 (fun act i -> acts.(i) < - actions.(act))
751757 t ;
752758 (fun ctx ->
759+ if ! Config. bs_only then
760+ Arg. make_switch ~offset: (ll+ ctx.off) loc ctx.arg tbl acts sw_names
761+ else
753762 match - ll- ctx.off with
754- | 0 -> Arg. make_switch loc ctx.arg tbl acts sw_names
763+ | 0 -> Arg. make_switch loc ctx.arg tbl acts sw_names ~offset: 0
755764 | _ ->
756765 Arg. bind
757766 (Arg. make_offset ctx.arg (- ll- ctx.off))
758- (fun arg -> Arg. make_switch loc arg tbl acts sw_names))
767+ (fun arg -> Arg. make_switch loc arg tbl acts sw_names ~offset: 0 ))
759768
760769
761770let make_clusters loc ({cases =cases ; actions =actions } as s ) n_clusters k sw_names =
0 commit comments