Module BTL_BlockOptimizeraux

module BTL_BlockOptimizeraux: sig .. end

Auxiliary function of the BTL prepass scheduler oracle


module SI: Stdlib.Set.Make(Stdlib.Int)
val is_a_cb : BTL.iblock -> bool
val is_a_load : BTL.iblock -> bool
val count_cbs : BTL.iblock array ->
BTL.iblock option ->
SI.elt array ->
(SI.elt, SI.t) Stdlib.Hashtbl.t
val find_array : 'a array -> 'a -> int
val apply_schedule : BTL.iblock array -> BTL.iblock option -> int array -> BTL.iblock
val reference_counting : (BTL.iblock * Registers.Regset.t) array ->
Registers.Regset.t ->
RTLtyping.regenv ->
(Registers.reg, int * int) Stdlib.Hashtbl.t *
(Registers.reg * bool) list array

the useful one. Returns a hashtable with bindings of shape ** (r,(t, n), where r is a pseudo-register (Registers.reg), ** t is its class (according to typing), and n the number of ** times it's referenced as an argument in instructions of seqa ; ** and an array containing the list of regs referenced by each ** instruction, with a boolean to know whether it's as arg or dest

val flatten_blk_basics : BTL.iblock_info -> BTL.iblock array * BTL.iblock option
val get_live_regs_entry : (BTL.iblock * Registers.Regset.t) array ->
BTL.iblock_info -> 'a -> Registers.Regset.t