ghc-7.2.1: The GHC API

RegAlloc.Liveness

Synopsis

Documentation

type RegMap a = UniqFM aSource

type LiveCmmTop statics instr = GenCmmTop statics LiveInfo [SCC (LiveBasicBlock instr)]Source

A top level thing which carries liveness information.

data InstrSR instr Source

The register allocator also wants to use SPILL/RELOAD meta instructions, so we'll keep those here.

Constructors

Instr instr

A real machine instruction

SPILL Reg Int

spill this reg to a stack slot

RELOAD Int Reg

reload this reg from a stack slot

Instances

data LiveInstr instr Source

An instruction with liveness information.

Constructors

LiveInstr (InstrSR instr) (Maybe Liveness) 

Instances

data Liveness Source

Liveness information. The regs which die are ones which are no longer live in the *next* instruction in this sequence. (NB. if the instruction is a jump, these registers might still be live at the jump target(s) - you have to check the liveness at the destination block to find out).

Constructors

Liveness

registers that died because they were clobbered by something.

Fields

liveBorn :: RegSet

registers born in this instruction (written to for first time).

liveDieRead :: RegSet

registers that died because they were read for the last time.

liveDieWrite :: RegSet
 

data LiveInfo Source

Stash regs live on entry to each basic block in the info part of the cmm code.

Instances

type LiveBasicBlock instr = GenBasicBlock (LiveInstr instr)Source

A basic block with liveness information.

mapBlockTop :: (LiveBasicBlock instr -> LiveBasicBlock instr) -> LiveCmmTop statics instr -> LiveCmmTop statics instrSource

map a function across all the basic blocks in this code

mapBlockTopM :: Monad m => (LiveBasicBlock instr -> m (LiveBasicBlock instr)) -> LiveCmmTop statics instr -> m (LiveCmmTop statics instr)Source

map a function across all the basic blocks in this code (monadic version)

mapSCCM :: Monad m => (a -> m b) -> SCC a -> m (SCC b)Source

mapGenBlockTopM :: Monad m => (GenBasicBlock i -> m (GenBasicBlock i)) -> GenCmmTop d h (ListGraph i) -> m (GenCmmTop d h (ListGraph i))Source

map a function across all the basic blocks in this code (monadic version)

stripLive :: (Outputable statics, PlatformOutputable instr, Instruction instr) => Platform -> LiveCmmTop statics instr -> NatCmmTop statics instrSource

Strip away liveness information, yielding NatCmmTop

stripLiveBlock :: Instruction instr => Platform -> LiveBasicBlock instr -> NatBasicBlock instrSource

Strip away liveness information from a basic block, and make real spill instructions out of SPILL, RELOAD pseudos along the way.

slurpConflicts :: Instruction instr => LiveCmmTop statics instr -> (Bag (UniqSet Reg), Bag (Reg, Reg))Source

Slurp out the list of register conflicts and reg-reg moves from this top level thing. Slurping of conflicts and moves is wrapped up together so we don't have to make two passes over the same code when we want to build the graph.

slurpReloadCoalesce :: forall statics instr. Instruction instr => LiveCmmTop statics instr -> Bag (Reg, Reg)Source

For spill/reloads

SPILL v1, slot1 ... RELOAD slot1, v2

If we can arrange that v1 and v2 are allocated to the same hreg it's more likely the spill/reload instrs can be cleaned and replaced by a nop reg-reg move.

eraseDeltasLive :: Instruction instr => LiveCmmTop statics instr -> LiveCmmTop statics instrSource

Erase Delta instructions.

patchEraseLive :: Instruction instr => (Reg -> Reg) -> LiveCmmTop statics instr -> LiveCmmTop statics instrSource

Patch the registers in this code according to this register mapping. also erase reg -> reg moves when the reg is the same. also erase reg -> reg moves when the destination dies in this instr.

patchRegsLiveInstr :: Instruction instr => (Reg -> Reg) -> LiveInstr instr -> LiveInstr instrSource

Patch registers in this LiveInstr, including the liveness information.

reverseBlocksInTops :: LiveCmmTop statics instr -> LiveCmmTop statics instrSource

If we've compute liveness info for this code already we have to reverse the SCCs in each top to get them back to the right order so we can do it again.

regLiveness :: (PlatformOutputable instr, Instruction instr) => Platform -> LiveCmmTop statics instr -> UniqSM (LiveCmmTop statics instr)Source

natCmmTopToLive :: Instruction instr => NatCmmTop statics instr -> LiveCmmTop statics instrSource

Convert a NatCmmTop to a LiveCmmTop, with empty liveness information