ghc-6.12.3: The GHC APISource codeContentsIndex
RegAlloc.Linear.Base
Description
Put common type definitions here to break recursive module dependencies.
Synopsis
type BlockAssignment = BlockMap (FreeRegs, RegMap Loc)
data Loc
= InReg !RealReg
| InMem !StackSlot
| InBoth !RealReg !StackSlot
regsOfLoc :: Loc -> [RealReg]
data SpillReason
= SpillAlloc !Unique
| SpillClobber !Unique
| SpillLoad !Unique
| SpillJoinRR !Unique
| SpillJoinRM !Unique
data RegAllocStats = RegAllocStats {
ra_spillInstrs :: UniqFM [Int]
}
data RA_State = RA_State {
ra_blockassig :: BlockAssignment
ra_freeregs :: !FreeRegs
ra_assig :: RegMap Loc
ra_delta :: Int
ra_stack :: StackMap
ra_us :: UniqSupply
ra_spills :: [SpillReason]
}
newtype RegM a = RegM {
unReg :: RA_State -> (#RA_State, a#)
}
Documentation
type BlockAssignment = BlockMap (FreeRegs, RegMap Loc)Source
Used to store the register assignment on entry to a basic block. We use this to handle join points, where multiple branch instructions target a particular label. We have to insert fixup code to make the register assignments from the different sources match up.
data Loc Source
Where a vreg is currently stored A temporary can be marked as living in both a register and memory (InBoth), for example if it was recently loaded from a spill location. This makes it cheap to spill (no save instruction required), but we have to be careful to turn this into InReg if the value in the register is changed.
Constructors
InReg !RealRegvreg is in a register
InMem !StackSlotvreg is held in a stack slot
InBoth !RealReg !StackSlotvreg is held in both a register and a stack slot
show/hide Instances
regsOfLoc :: Loc -> [RealReg]Source
Get the reg numbers stored in this Loc.
data SpillReason Source
Reasons why instructions might be inserted by the spiller. Used when generating stats for -ddrop-asm-stats.
Constructors
SpillAlloc !Uniquevreg was spilled to a slot so we could use its current hreg for another vreg
SpillClobber !Uniquevreg was moved because its hreg was clobbered
SpillLoad !Uniquevreg was loaded from a spill slot
SpillJoinRR !Uniquereg-reg move inserted during join to targets
SpillJoinRM !Uniquereg-mem move inserted during join to targets
data RegAllocStats Source
Used to carry interesting stats out of the register allocator.
Constructors
RegAllocStats
ra_spillInstrs :: UniqFM [Int]
data RA_State Source
The register alloctor state
Constructors
RA_State
ra_blockassig :: BlockAssignmentthe current mapping from basic blocks to the register assignments at the beginning of that block.
ra_freeregs :: !FreeRegsfree machine registers
ra_assig :: RegMap Locassignment of temps to locations
ra_delta :: Intcurrent stack delta
ra_stack :: StackMapfree stack slots for spilling
ra_us :: UniqSupplyunique supply for generating names for join point fixup blocks.
ra_spills :: [SpillReason]Record why things were spilled, for -ddrop-asm-stats. Just keep a list here instead of a map of regs -> reasons. We don't want to slow down the allocator if we're not going to emit the stats.
newtype RegM a Source
The register allocator monad type.
Constructors
RegM
unReg :: RA_State -> (#RA_State, a#)
show/hide Instances
Produced by Haddock version 2.6.1