ghc-6.10.2: The GHC APIContentsIndex
RegLiveness
Synopsis
type RegSet = UniqSet Reg
type RegMap a = UniqFM a
emptyRegMap :: UniqFM a
type BlockMap a = UniqFM a
emptyBlockMap :: UniqFM a
type LiveCmmTop = GenCmmTop CmmStatic LiveInfo (ListGraph (GenBasicBlock LiveInstr))
data LiveInstr = Instr Instr (Maybe Liveness)
data Liveness = Liveness {
liveBorn :: RegSet
liveDieRead :: RegSet
liveDieWrite :: RegSet
}
data LiveInfo = LiveInfo [CmmStatic] (Maybe BlockId) (BlockMap RegSet)
type LiveBasicBlock = GenBasicBlock LiveInstr
mapBlockTop :: (LiveBasicBlock -> LiveBasicBlock) -> LiveCmmTop -> LiveCmmTop
mapBlockTopM :: Monad m => (LiveBasicBlock -> m LiveBasicBlock) -> LiveCmmTop -> m LiveCmmTop
mapGenBlockTop :: (GenBasicBlock i -> GenBasicBlock i) -> GenCmmTop d h (ListGraph i) -> GenCmmTop d h (ListGraph i)
mapGenBlockTopM :: Monad m => (GenBasicBlock i -> m (GenBasicBlock i)) -> GenCmmTop d h (ListGraph i) -> m (GenCmmTop d h (ListGraph i))
stripLive :: LiveCmmTop -> NatCmmTop
spillNatBlock :: NatBasicBlock -> NatBasicBlock
slurpConflicts :: LiveCmmTop -> (Bag (UniqSet Reg), Bag (Reg, Reg))
slurpReloadCoalesce :: LiveCmmTop -> Bag (Reg, Reg)
eraseDeltasLive :: LiveCmmTop -> LiveCmmTop
patchEraseLive :: (Reg -> Reg) -> LiveCmmTop -> LiveCmmTop
patchRegsLiveInstr :: (Reg -> Reg) -> LiveInstr -> LiveInstr
regLiveness :: NatCmmTop -> UniqSM LiveCmmTop
Documentation
type RegSet = UniqSet Reg
type RegMap a = UniqFM a
emptyRegMap :: UniqFM a
type BlockMap a = UniqFM a
emptyBlockMap :: UniqFM a
type LiveCmmTop = GenCmmTop CmmStatic LiveInfo (ListGraph (GenBasicBlock LiveInstr))
A top level thing which carries liveness information.
data LiveInstr
An instruction with liveness information.
Constructors
Instr Instr (Maybe Liveness)
show/hide Instances
data Liveness
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
Livenessregisters that died because they were clobbered by something.
liveBorn :: RegSetregisters born in this instruction (written to for first time).
liveDieRead :: RegSetregisters that died because they were read for the last time.
liveDieWrite :: RegSet
data LiveInfo
Stash regs live on entry to each basic block in the info part of the cmm code.
Constructors
LiveInfo [CmmStatic] (Maybe BlockId) (BlockMap RegSet)
show/hide Instances
type LiveBasicBlock = GenBasicBlock LiveInstr
A basic block with liveness information.
mapBlockTop :: (LiveBasicBlock -> LiveBasicBlock) -> LiveCmmTop -> LiveCmmTop
map a function across all the basic blocks in this code
mapBlockTopM :: Monad m => (LiveBasicBlock -> m LiveBasicBlock) -> LiveCmmTop -> m LiveCmmTop
map a function across all the basic blocks in this code (monadic version)
mapGenBlockTop :: (GenBasicBlock i -> GenBasicBlock i) -> GenCmmTop d h (ListGraph i) -> GenCmmTop d h (ListGraph i)
mapGenBlockTopM :: Monad m => (GenBasicBlock i -> m (GenBasicBlock i)) -> GenCmmTop d h (ListGraph i) -> m (GenCmmTop d h (ListGraph i))
map a function across all the basic blocks in this code (monadic version)
stripLive :: LiveCmmTop -> NatCmmTop
Strip away liveness information, yielding NatCmmTop
spillNatBlock :: NatBasicBlock -> NatBasicBlock
Make real spill instructions out of SPILL, RELOAD pseudos
slurpConflicts :: LiveCmmTop -> (Bag (UniqSet Reg), Bag (Reg, Reg))
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 :: LiveCmmTop -> Bag (Reg, Reg)

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 :: LiveCmmTop -> LiveCmmTop
Erase Delta instructions.
patchEraseLive :: (Reg -> Reg) -> LiveCmmTop -> LiveCmmTop
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 :: (Reg -> Reg) -> LiveInstr -> LiveInstr
Patch registers in this LiveInstr, including the liveness information.
regLiveness :: NatCmmTop -> UniqSM LiveCmmTop
Produced by Haddock version 2.4.2