Skip to content

Commit c812d15

Browse files
committed
removed exit_label ref
1 parent d880e52 commit c812d15

File tree

1 file changed

+38
-42
lines changed

1 file changed

+38
-42
lines changed

asmcomp/linearize.ml

Lines changed: 38 additions & 42 deletions
Original file line numberDiff line numberDiff line change
@@ -110,87 +110,85 @@ let add_branch lbl n =
110110

111111
(* Association list: exit handler -> (handler label, try-nesting factor) *)
112112

113-
let exit_label = ref []
114-
115-
let find_exit_label_try_depth k =
113+
let find_exit_label_try_depth k ~exit_label =
116114
try
117-
List.assoc k !exit_label
115+
List.assoc k exit_label
118116
with
119117
| Not_found -> Misc.fatal_error "Linearize.find_exit_label"
120118

121-
let find_exit_label k ~try_depth =
122-
let (label, t) = find_exit_label_try_depth k in
119+
let find_exit_label k ~try_depth ~exit_label =
120+
let (label, t) = find_exit_label_try_depth k ~exit_label in
123121
assert(t = try_depth);
124122
label
125123

126-
let is_next_catch n ~try_depth = match !exit_label with
124+
let is_next_catch n ~try_depth ~exit_label = match exit_label with
127125
| (n0,(_,t))::_ when n0=n && t = try_depth -> true
128126
| _ -> false
129127

130-
let local_exit k ~try_depth =
131-
snd (find_exit_label_try_depth k) = try_depth
128+
let local_exit k ~try_depth ~exit_label =
129+
snd (find_exit_label_try_depth k ~exit_label) = try_depth
132130

133131
(* Linearize an instruction [i]: add it in front of the continuation [n] *)
134132
let linear i n contains_calls =
135-
let rec linear i n ~try_depth =
133+
let rec linear i n ~try_depth ~exit_label =
136134
match i.Mach.desc with
137135
Iend -> n
138136
| Iop(Itailcall_ind _ | Itailcall_imm _ as op) ->
139137
if not Config.spacetime then
140138
copy_instr (Lop op) i (discard_dead_code n)
141139
else
142-
copy_instr (Lop op) i (linear i.Mach.next n ~try_depth)
140+
copy_instr (Lop op) i (linear i.Mach.next n ~try_depth ~exit_label)
143141
| Iop(Imove | Ireload | Ispill)
144142
when i.Mach.arg.(0).loc = i.Mach.res.(0).loc ->
145-
linear i.Mach.next n ~try_depth
143+
linear i.Mach.next n ~try_depth ~exit_label
146144
| Iop op ->
147-
copy_instr (Lop op) i (linear i.Mach.next n ~try_depth)
145+
copy_instr (Lop op) i (linear i.Mach.next n ~try_depth ~exit_label)
148146
| Ireturn ->
149147
let n1 = copy_instr Lreturn i (discard_dead_code n) in
150148
if contains_calls
151149
then cons_instr Lreloadretaddr n1
152150
else n1
153151
| Iifthenelse(test, ifso, ifnot) ->
154-
let n1 = linear i.Mach.next n ~try_depth in
152+
let n1 = linear i.Mach.next n ~try_depth ~exit_label in
155153
begin match (ifso.Mach.desc, ifnot.Mach.desc, n1.desc) with
156154
Iend, _, Lbranch lbl ->
157-
copy_instr (Lcondbranch(test, lbl)) i (linear ifnot n1 ~try_depth)
155+
copy_instr (Lcondbranch(test, lbl)) i (linear ifnot n1 ~try_depth ~exit_label)
158156
| _, Iend, Lbranch lbl ->
159-
copy_instr (Lcondbranch(invert_test test, lbl)) i (linear ifso n1 ~try_depth)
157+
copy_instr (Lcondbranch(invert_test test, lbl)) i (linear ifso n1 ~try_depth ~exit_label)
160158
| Iexit nfail1, Iexit nfail2, _
161-
when is_next_catch nfail1 ~try_depth && local_exit nfail2 ~try_depth->
162-
let lbl2 = find_exit_label nfail2 ~try_depth:0 in
159+
when is_next_catch nfail1 ~try_depth ~exit_label && local_exit nfail2 ~try_depth ~exit_label->
160+
let lbl2 = find_exit_label nfail2 ~try_depth:0 ~exit_label in
163161
copy_instr
164-
(Lcondbranch (invert_test test, lbl2)) i (linear ifso n1 ~try_depth)
165-
| Iexit nfail, _, _ when local_exit nfail ~try_depth->
166-
let n2 = linear ifnot n1 ~try_depth
167-
and lbl = find_exit_label nfail ~try_depth:0 in
162+
(Lcondbranch (invert_test test, lbl2)) i (linear ifso n1 ~try_depth ~exit_label)
163+
| Iexit nfail, _, _ when local_exit nfail ~try_depth ~exit_label->
164+
let n2 = linear ifnot n1 ~try_depth ~exit_label
165+
and lbl = find_exit_label nfail ~try_depth:0 ~exit_label in
168166
copy_instr (Lcondbranch(test, lbl)) i n2
169-
| _, Iexit nfail, _ when local_exit nfail ~try_depth->
170-
let n2 = linear ifso n1 ~try_depth in
171-
let lbl = find_exit_label nfail ~try_depth:0 in
167+
| _, Iexit nfail, _ when local_exit nfail ~try_depth ~exit_label->
168+
let n2 = linear ifso n1 ~try_depth ~exit_label in
169+
let lbl = find_exit_label nfail ~try_depth:0 ~exit_label in
172170
copy_instr (Lcondbranch(invert_test test, lbl)) i n2
173171
| Iend, _, _ ->
174172
let (lbl_end, n2) = get_label n1 in
175-
copy_instr (Lcondbranch(test, lbl_end)) i (linear ifnot n2 ~try_depth)
173+
copy_instr (Lcondbranch(test, lbl_end)) i (linear ifnot n2 ~try_depth ~exit_label)
176174
| _, Iend, _ ->
177175
let (lbl_end, n2) = get_label n1 in
178176
copy_instr (Lcondbranch(invert_test test, lbl_end)) i
179-
(linear ifso n2 ~try_depth)
177+
(linear ifso n2 ~try_depth ~exit_label)
180178
| _, _, _ ->
181179
(* Should attempt branch prediction here *)
182180
let (lbl_end, n2) = get_label n1 in
183-
let (lbl_else, nelse) = get_label (linear ifnot n2 ~try_depth) in
181+
let (lbl_else, nelse) = get_label (linear ifnot n2 ~try_depth ~exit_label) in
184182
copy_instr (Lcondbranch(invert_test test, lbl_else)) i
185-
(linear ifso (add_branch lbl_end nelse) ~try_depth)
183+
(linear ifso (add_branch lbl_end nelse) ~try_depth ~exit_label)
186184
end
187185
| Iswitch(index, cases) ->
188186
let lbl_cases = Array.make (Array.length cases) 0 in
189-
let (lbl_end, n1) = get_label(linear i.Mach.next n ~try_depth) in
187+
let (lbl_end, n1) = get_label(linear i.Mach.next n ~try_depth ~exit_label) in
190188
let n2 = ref (discard_dead_code n1) in
191189
for i = Array.length cases - 1 downto 0 do
192190
let (lbl_case, ncase) =
193-
get_label(linear cases.(i) (add_branch lbl_end !n2) ~try_depth) in
191+
get_label(linear cases.(i) (add_branch lbl_end !n2) ~try_depth ~exit_label) in
194192
lbl_cases.(i) <- lbl_case;
195193
n2 := discard_dead_code ncase
196194
done;
@@ -206,7 +204,7 @@ let linear i n contains_calls =
206204
end else
207205
copy_instr (Lswitch(Array.map (fun n -> lbl_cases.(n)) index)) i !n2
208206
| Icatch(_rec_flag, handlers, body) ->
209-
let (lbl_end, n1) = get_label(linear i.Mach.next n ~try_depth) in
207+
let (lbl_end, n1) = get_label(linear i.Mach.next n ~try_depth ~exit_label) in
210208
(* CR mshinwell for pchambart:
211209
1. rename "io"
212210
2. Make sure the test cases cover the "Iend" cases too *)
@@ -218,20 +216,18 @@ let linear i n contains_calls =
218216
let exit_label_add = List.map2
219217
(fun (nfail, _) lbl -> (nfail, (lbl, try_depth)))
220218
handlers labels_at_entry_to_handlers in
221-
let previous_exit_label = !exit_label in
222-
exit_label := exit_label_add @ !exit_label;
219+
let previous_exit_label = List.append exit_label exit_label_add in
223220
let n2 = List.fold_left2 (fun n (_nfail, handler) lbl_handler ->
224221
match handler.Mach.desc with
225222
| Iend -> n
226223
| _ -> cons_instr (Llabel lbl_handler)
227-
(linear handler (add_branch lbl_end n) ~try_depth))
224+
(linear handler (add_branch lbl_end n) ~try_depth ~exit_label))
228225
n1 handlers labels_at_entry_to_handlers
229226
in
230-
let n3 = linear body (add_branch lbl_end n2) ~try_depth in
231-
exit_label := previous_exit_label;
227+
let n3 = linear body (add_branch lbl_end n2) ~try_depth ~exit_label:previous_exit_label in
232228
n3
233229
| Iexit nfail ->
234-
let lbl, t = find_exit_label_try_depth nfail in
230+
let lbl, t = find_exit_label_try_depth nfail ~exit_label in
235231
assert (i.Mach.next.desc = Mach.Iend);
236232
let delta_traps = try_depth - t in
237233
let n1 = adjust_trap_depth delta_traps n in
@@ -241,21 +237,21 @@ let linear i n contains_calls =
241237
in
242238
loop (add_branch lbl n1) try_depth
243239
| Itrywith(body, handler) ->
244-
let (lbl_join, n1) = get_label (linear i.Mach.next n ~try_depth) in
240+
let (lbl_join, n1) = get_label (linear i.Mach.next n ~try_depth ~exit_label) in
245241
let (lbl_handler, n2) =
246-
get_label (cons_instr Lentertrap (linear handler n1 ~try_depth))
242+
get_label (cons_instr Lentertrap (linear handler n1 ~try_depth ~exit_label))
247243
in
248244
assert (i.Mach.arg = [| |] || Config.spacetime);
249245
let n3 = cons_instr (Lpushtrap { lbl_handler; })
250246
(linear body
251247
(cons_instr
252248
Lpoptrap
253-
(add_branch lbl_join n2)) ~try_depth:(try_depth + 1)) in
249+
(add_branch lbl_join n2)) ~try_depth:(try_depth + 1) ~exit_label) in
254250
n3
255251

256252
| Iraise k ->
257253
copy_instr (Lraise k) i (discard_dead_code n)
258-
in linear i n ~try_depth:0
254+
in linear i n ~try_depth:0 ~exit_label:[]
259255

260256
let add_prologue first_insn prologue_required =
261257
(* The prologue needs to come after any [Iname_for_debugger] operations that

0 commit comments

Comments
 (0)