ghc-6.12.3: The GHC APISource codeContentsIndex
Instruction
Synopsis
data RegUsage = RU [Reg] [Reg]
noUsage :: RegUsage
type NatCmm instr = GenCmm CmmStatic [CmmStatic] (ListGraph instr)
type NatCmmTop instr = GenCmmTop CmmStatic [CmmStatic] (ListGraph instr)
type NatBasicBlock instr = GenBasicBlock instr
class Instruction instr where
regUsageOfInstr :: instr -> RegUsage
patchRegsOfInstr :: instr -> (Reg -> Reg) -> instr
isJumpishInstr :: instr -> Bool
jumpDestsOfInstr :: instr -> [BlockId]
patchJumpInstr :: instr -> (BlockId -> BlockId) -> instr
mkSpillInstr :: Reg -> Int -> Int -> instr
mkLoadInstr :: Reg -> Int -> Int -> instr
takeDeltaInstr :: instr -> Maybe Int
isMetaInstr :: instr -> Bool
mkRegRegMoveInstr :: Reg -> Reg -> instr
takeRegRegMoveInstr :: instr -> Maybe (Reg, Reg)
mkJumpInstr :: BlockId -> [instr]
Documentation
data RegUsage Source

Holds a list of source and destination registers used by a particular instruction.

Machine registers that are pre-allocated to stgRegs are filtered out, because they are uninteresting from a register allocation standpoint. (We wouldn't want them to end up on the free list!)

As far as we are concerned, the fixed registers simply don't exist (for allocation purposes, anyway).

Constructors
RU [Reg] [Reg]
noUsage :: RegUsageSource
No regs read or written to.
type NatCmm instr = GenCmm CmmStatic [CmmStatic] (ListGraph instr)Source
type NatCmmTop instr = GenCmmTop CmmStatic [CmmStatic] (ListGraph instr)Source
type NatBasicBlock instr = GenBasicBlock instrSource
class Instruction instr whereSource
Common things that we can do with instructions, on all architectures. These are used by the shared parts of the native code generator, specifically the register allocators.
Methods
regUsageOfInstr :: instr -> RegUsageSource
Get the registers that are being used by this instruction. regUsage doesn't need to do any trickery for jumps and such. Just state precisely the regs read and written by that insn. The consequences of control flow transfers, as far as register allocation goes, are taken care of by the register allocator.
patchRegsOfInstr :: instr -> (Reg -> Reg) -> instrSource
Apply a given mapping to all the register references in this instruction.
isJumpishInstr :: instr -> BoolSource
Checks whether this instruction is a jump/branch instruction. One that can change the flow of control in a way that the register allocator needs to worry about.
jumpDestsOfInstr :: instr -> [BlockId]Source
Give the possible destinations of this jump instruction. Must be defined for all jumpish instructions.
patchJumpInstr :: instr -> (BlockId -> BlockId) -> instrSource
Change the destination of this jump instruction. Used in the linear allocator when adding fixup blocks for join points.
mkSpillInstrSource
:: Regthe reg to spill
-> Intthe current stack delta
-> Intspill slot to use
-> instr
An instruction to spill a register into a spill slot.
mkLoadInstrSource
:: Regthe reg to reload.
-> Intthe current stack delta
-> Intthe spill slot to use
-> instr
An instruction to reload a register from a spill slot.
takeDeltaInstr :: instr -> Maybe IntSource
See if this instruction is telling us the current C stack delta
isMetaInstr :: instr -> BoolSource

Check whether this instruction is some meta thing inserted into the instruction stream for other purposes.

Not something that has to be treated as a real machine instruction and have its registers allocated.

eg, comments, delta, ldata, etc.

mkRegRegMoveInstrSource
:: Regsource register
-> Regdestination register
-> instr
Copy the value in a register to another one. Must work for all register classes.
takeRegRegMoveInstr :: instr -> Maybe (Reg, Reg)Source
Take the source and destination from this reg -> reg move instruction or Nothing if it's not one
mkJumpInstr :: BlockId -> [instr]Source
Make an unconditional jump instruction. For architectures with branch delay slots, its ok to put a NOP after the jump. Don't fill the delay slot with an instruction that references regs or you'll confuse the linear allocator.
show/hide Instances
Produced by Haddock version 2.6.1