Skip to content

Commit

Permalink
Collect the constrained registers into a set.
Browse files Browse the repository at this point in the history
Sets allow for faster insertion than ordered lists, while also supporting
iteration according to the comparison function.

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@13150 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
  • Loading branch information
bmeurer committed Dec 21, 2012
1 parent 6fad047 commit 6d46c66
Showing 1 changed file with 13 additions and 8 deletions.
21 changes: 13 additions & 8 deletions asmcomp/coloring.ml
Expand Up @@ -12,6 +12,15 @@

(* Register allocation by coloring of the interference graph *)

module OrderedRegSet =
Set.Make(struct
type t = Reg.t
let compare r1 r2 =
let open Reg in
let n = r2.spill_cost * r1.degree - r1.spill_cost * r2.degree in
if n <> 0 then n else r1.stamp - r2.stamp
end)

open Reg

let allocate_registers() =
Expand All @@ -20,7 +29,7 @@ let allocate_registers() =
sorted by spill cost (highest first).
The spill cost measure is [r.spill_cost / r.degree].
[r.spill_cost] estimates the number of accesses to [r]. *)
let constrained = ref [] in
let constrained = ref OrderedRegSet.empty in

(* Unconstrained regs with degree < number of available registers *)
let unconstrained = ref [] in
Expand All @@ -47,11 +56,7 @@ let allocate_registers() =
end else if reg.degree < Proc.num_available_registers.(cl) then
unconstrained := reg :: !unconstrained
else begin
let rec insert_sorted r = function
r' :: l when r.spill_cost * r'.degree < r'.spill_cost * r.degree ->
r' :: insert_sorted r l
| l -> r :: l in
constrained := insert_sorted reg !constrained
constrained := OrderedRegSet.add reg !constrained
end in

(* Iterate over all registers preferred by the given register (transitive) *)
Expand Down Expand Up @@ -210,5 +215,5 @@ let allocate_registers() =
Second pass: assign locations to constrained regs
Third pass: assign locations to unconstrained regs *)
List.iter remove_reg (Reg.all_registers());
List.iter assign_location (!constrained);
List.iter assign_location (!unconstrained)
OrderedRegSet.iter assign_location !constrained;
List.iter assign_location !unconstrained

0 comments on commit 6d46c66

Please sign in to comment.