ghc-6.12.2: The GHC APISource codeContentsIndex
RegAlloc.Linear.State
Description
State monad for the linear register allocator.
Synopsis
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]
}
data RegM a
runR :: BlockAssignment -> FreeRegs -> RegMap Loc -> StackMap -> UniqSupply -> RegM a -> (BlockAssignment, StackMap, RegAllocStats, a)
spillR :: Instruction instr => Reg -> Unique -> RegM (instr, Int)
loadR :: Instruction instr => Reg -> Int -> RegM instr
getFreeRegsR :: RegM FreeRegs
setFreeRegsR :: FreeRegs -> RegM ()
getAssigR :: RegM (RegMap Loc)
setAssigR :: RegMap Loc -> RegM ()
getBlockAssigR :: RegM BlockAssignment
setBlockAssigR :: BlockAssignment -> RegM ()
setDeltaR :: Int -> RegM ()
getDeltaR :: RegM Int
getUniqueR :: RegM Unique
recordSpill :: SpillReason -> RegM ()
Documentation
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.
data RegM a Source
The register allocator monad type.
show/hide Instances
runR :: BlockAssignment -> FreeRegs -> RegMap Loc -> StackMap -> UniqSupply -> RegM a -> (BlockAssignment, StackMap, RegAllocStats, a)Source
Run a computation in the RegM register allocator monad.
spillR :: Instruction instr => Reg -> Unique -> RegM (instr, Int)Source
loadR :: Instruction instr => Reg -> Int -> RegM instrSource
getFreeRegsR :: RegM FreeRegsSource
setFreeRegsR :: FreeRegs -> RegM ()Source
getAssigR :: RegM (RegMap Loc)Source
setAssigR :: RegMap Loc -> RegM ()Source
getBlockAssigR :: RegM BlockAssignmentSource
setBlockAssigR :: BlockAssignment -> RegM ()Source
setDeltaR :: Int -> RegM ()Source
getDeltaR :: RegM IntSource
getUniqueR :: RegM UniqueSource
recordSpill :: SpillReason -> RegM ()Source
Record that a spill instruction was inserted, for profiling.
Produced by Haddock version 2.6.1