Liveness and Deadcode refactoring (#670)
parent
9d77b268ed
commit
5af8dc6ad6
|
@ -22,32 +22,33 @@ open Mach
|
|||
and a set of registers live "before" instruction [i]. *)
|
||||
|
||||
let rec deadcode i =
|
||||
let arg = i.arg in
|
||||
match i.desc with
|
||||
| Iend | Ireturn | Iop(Itailcall_ind _) | Iop(Itailcall_imm _) | Iraise _ ->
|
||||
(i, Reg.add_set_array i.live i.arg)
|
||||
(i, Reg.add_set_array i.live arg)
|
||||
| Iop op ->
|
||||
let (s, before) = deadcode i.next in
|
||||
if Proc.op_is_pure op (* no side effects *)
|
||||
&& Reg.disjoint_set_array before i.res (* results are not used after *)
|
||||
&& not (Proc.regs_are_volatile i.arg) (* no stack-like hard reg *)
|
||||
&& not (Proc.regs_are_volatile arg) (* no stack-like hard reg *)
|
||||
&& not (Proc.regs_are_volatile i.res) (* is involved *)
|
||||
then begin
|
||||
assert (Array.length i.res > 0); (* sanity check *)
|
||||
(s, before)
|
||||
end else begin
|
||||
({i with next = s}, Reg.add_set_array i.live i.arg)
|
||||
({i with next = s}, Reg.add_set_array i.live arg)
|
||||
end
|
||||
| Iifthenelse(test, ifso, ifnot) ->
|
||||
let (ifso', _) = deadcode ifso in
|
||||
let (ifnot', _) = deadcode ifnot in
|
||||
let (s, _) = deadcode i.next in
|
||||
({i with desc = Iifthenelse(test, ifso', ifnot'); next = s},
|
||||
Reg.add_set_array i.live i.arg)
|
||||
Reg.add_set_array i.live arg)
|
||||
| Iswitch(index, cases) ->
|
||||
let cases' = Array.map (fun c -> fst (deadcode c)) cases in
|
||||
let (s, _) = deadcode i.next in
|
||||
({i with desc = Iswitch(index, cases'); next = s},
|
||||
Reg.add_set_array i.live i.arg)
|
||||
Reg.add_set_array i.live arg)
|
||||
| Iloop(body) ->
|
||||
let (body', _) = deadcode body in
|
||||
let (s, _) = deadcode i.next in
|
||||
|
|
|
@ -35,18 +35,19 @@ let rec live i finally =
|
|||
before the instruction sequence.
|
||||
The instruction i is annotated by the set of registers live across
|
||||
the instruction. *)
|
||||
let arg = i.arg in
|
||||
match i.desc with
|
||||
Iend ->
|
||||
i.live <- finally;
|
||||
finally
|
||||
| Ireturn | Iop(Itailcall_ind _) | Iop(Itailcall_imm _) ->
|
||||
i.live <- Reg.Set.empty; (* no regs are live across *)
|
||||
Reg.set_of_array i.arg
|
||||
Reg.set_of_array arg
|
||||
| Iop op ->
|
||||
let after = live i.next finally in
|
||||
if Proc.op_is_pure op (* no side effects *)
|
||||
&& Reg.disjoint_set_array after i.res (* results are not used after *)
|
||||
&& not (Proc.regs_are_volatile i.arg) (* no stack-like hard reg *)
|
||||
&& not (Proc.regs_are_volatile arg) (* no stack-like hard reg *)
|
||||
&& not (Proc.regs_are_volatile i.res) (* is involved *)
|
||||
then begin
|
||||
(* This operation is dead code. Ignore its arguments. *)
|
||||
|
@ -66,13 +67,13 @@ let rec live i finally =
|
|||
| _ ->
|
||||
across_after in
|
||||
i.live <- across;
|
||||
Reg.add_set_array across i.arg
|
||||
Reg.add_set_array across arg
|
||||
end
|
||||
| Iifthenelse(_test, ifso, ifnot) ->
|
||||
let at_join = live i.next finally in
|
||||
let at_fork = Reg.Set.union (live ifso at_join) (live ifnot at_join) in
|
||||
i.live <- at_fork;
|
||||
Reg.add_set_array at_fork i.arg
|
||||
Reg.add_set_array at_fork arg
|
||||
| Iswitch(_index, cases) ->
|
||||
let at_join = live i.next finally in
|
||||
let at_fork = ref Reg.Set.empty in
|
||||
|
@ -80,7 +81,7 @@ let rec live i finally =
|
|||
at_fork := Reg.Set.union !at_fork (live cases.(i) at_join)
|
||||
done;
|
||||
i.live <- !at_fork;
|
||||
Reg.add_set_array !at_fork i.arg
|
||||
Reg.add_set_array !at_fork arg
|
||||
| Iloop(body) ->
|
||||
let at_top = ref Reg.Set.empty in
|
||||
(* Yes, there are better algorithms, but we'll just iterate till
|
||||
|
@ -120,7 +121,7 @@ let rec live i finally =
|
|||
before_body
|
||||
| Iraise _ ->
|
||||
i.live <- !live_at_raise;
|
||||
Reg.add_set_array !live_at_raise i.arg
|
||||
Reg.add_set_array !live_at_raise arg
|
||||
|
||||
let reset () =
|
||||
live_at_raise := Reg.Set.empty;
|
||||
|
|
Loading…
Reference in New Issue