Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Instr
- = COMMENT FastString
- | LOCATION Int Int Int String
- | LDATA Section RawCmmStatics
- | NEWBLOCK BlockId
- | DELTA Int
- | LD Format Reg AddrMode
- | LDFAR Format Reg AddrMode
- | LDR Format Reg AddrMode
- | LA Format Reg AddrMode
- | ST Format Reg AddrMode
- | STFAR Format Reg AddrMode
- | STU Format Reg AddrMode
- | STC Format Reg AddrMode
- | LIS Reg Imm
- | LI Reg Imm
- | MR Reg Reg
- | CMP Format Reg RI
- | CMPL Format Reg RI
- | BCC Cond BlockId (Maybe Bool)
- | BCCFAR Cond BlockId (Maybe Bool)
- | JMP CLabel [Reg]
- | MTCTR Reg
- | BCTR [Maybe BlockId] (Maybe CLabel) [Reg]
- | BL CLabel [Reg]
- | BCTRL [Reg]
- | ADD Reg Reg RI
- | ADDO Reg Reg Reg
- | ADDC Reg Reg Reg
- | ADDE Reg Reg Reg
- | ADDZE Reg Reg
- | ADDIS Reg Reg Imm
- | SUBF Reg Reg Reg
- | SUBFO Reg Reg Reg
- | SUBFC Reg Reg RI
- | SUBFE Reg Reg Reg
- | MULL Format Reg Reg RI
- | MULLO Format Reg Reg Reg
- | MFOV Format Reg
- | MULHU Format Reg Reg Reg
- | DIV Format Bool Reg Reg Reg
- | AND Reg Reg RI
- | ANDC Reg Reg Reg
- | NAND Reg Reg Reg
- | OR Reg Reg RI
- | ORIS Reg Reg Imm
- | XOR Reg Reg RI
- | XORIS Reg Reg Imm
- | EXTS Format Reg Reg
- | CNTLZ Format Reg Reg
- | NEG Reg Reg
- | NOT Reg Reg
- | SL Format Reg Reg RI
- | SR Format Reg Reg RI
- | SRA Format Reg Reg RI
- | RLWINM Reg Reg Int Int Int
- | CLRLI Format Reg Reg Int
- | CLRRI Format Reg Reg Int
- | FADD Format Reg Reg Reg
- | FSUB Format Reg Reg Reg
- | FMUL Format Reg Reg Reg
- | FDIV Format Reg Reg Reg
- | FABS Reg Reg
- | FNEG Reg Reg
- | FCMP Reg Reg
- | FCTIWZ Reg Reg
- | FCTIDZ Reg Reg
- | FCFID Reg Reg
- | FRSP Reg Reg
- | CRNOR Int Int Int
- | MFCR Reg
- | MFLR Reg
- | FETCHPC Reg
- | HWSYNC
- | ISYNC
- | LWSYNC
- | NOP
- data RI
- archWordFormat :: Bool -> Format
- stackFrameHeaderSize :: Platform -> Int
- maxSpillSlots :: NCGConfig -> Int
- allocMoreStack :: Platform -> Int -> NatCmmDecl statics Instr -> UniqSM (NatCmmDecl statics Instr, [(BlockId, BlockId)])
- makeFarBranches :: LabelMap RawCmmStatics -> [NatBasicBlock Instr] -> [NatBasicBlock Instr]
- mkJumpInstr :: BlockId -> [Instr]
- mkLoadInstr :: NCGConfig -> Reg -> Int -> Int -> [Instr]
- mkSpillInstr :: NCGConfig -> Reg -> Int -> Int -> [Instr]
- patchJumpInstr :: Instr -> (BlockId -> BlockId) -> Instr
- patchRegsOfInstr :: Instr -> (Reg -> Reg) -> Instr
- jumpDestsOfInstr :: Instr -> [BlockId]
- takeRegRegMoveInstr :: Instr -> Maybe (Reg, Reg)
- takeDeltaInstr :: Instr -> Maybe Int
- mkRegRegMoveInstr :: Reg -> Reg -> Instr
- mkStackAllocInstr :: Platform -> Int -> [Instr]
- mkStackDeallocInstr :: Platform -> Int -> [Instr]
- regUsageOfInstr :: Platform -> Instr -> RegUsage
- isJumpishInstr :: Instr -> Bool
- isMetaInstr :: Instr -> Bool
Documentation
Instances
Instruction Instr Source # | Instruction instance for powerpc |
Defined in GHC.CmmToAsm.PPC regUsageOfInstr :: Platform -> Instr -> RegUsage Source # patchRegsOfInstr :: Instr -> (Reg -> Reg) -> Instr Source # isJumpishInstr :: Instr -> Bool Source # jumpDestsOfInstr :: Instr -> [BlockId] Source # patchJumpInstr :: Instr -> (BlockId -> BlockId) -> Instr Source # mkSpillInstr :: NCGConfig -> Reg -> Int -> Int -> [Instr] Source # mkLoadInstr :: NCGConfig -> Reg -> Int -> Int -> [Instr] Source # takeDeltaInstr :: Instr -> Maybe Int Source # isMetaInstr :: Instr -> Bool Source # mkRegRegMoveInstr :: Platform -> Reg -> Reg -> Instr Source # takeRegRegMoveInstr :: Instr -> Maybe (Reg, Reg) Source # mkJumpInstr :: BlockId -> [Instr] Source # mkStackAllocInstr :: Platform -> Int -> [Instr] Source # mkStackDeallocInstr :: Platform -> Int -> [Instr] Source # |
archWordFormat :: Bool -> Format Source #
stackFrameHeaderSize :: Platform -> Int Source #
The size of a minimal stackframe header including minimal parameter save area.
maxSpillSlots :: NCGConfig -> Int Source #
The number of spill slots available without allocating more.
allocMoreStack :: Platform -> Int -> NatCmmDecl statics Instr -> UniqSM (NatCmmDecl statics Instr, [(BlockId, BlockId)]) Source #
makeFarBranches :: LabelMap RawCmmStatics -> [NatBasicBlock Instr] -> [NatBasicBlock Instr] Source #
mkJumpInstr :: BlockId -> [Instr] Source #
Make an unconditional jump instruction.
mkSpillInstr :: NCGConfig -> Reg -> Int -> Int -> [Instr] Source #
An instruction to spill a register into a spill slot.
patchJumpInstr :: Instr -> (BlockId -> BlockId) -> Instr Source #
Change the destination of this jump instruction. Used in the linear allocator when adding fixup blocks for join points.
patchRegsOfInstr :: Instr -> (Reg -> Reg) -> Instr Source #
Apply a given mapping to all the register references in this instruction.
jumpDestsOfInstr :: Instr -> [BlockId] Source #
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.
takeRegRegMoveInstr :: Instr -> Maybe (Reg, Reg) Source #
Take the source and destination from this reg -> reg move instruction or Nothing if it's not one
takeDeltaInstr :: Instr -> Maybe Int Source #
See if this instruction is telling us the current C stack delta
mkRegRegMoveInstr :: Reg -> Reg -> Instr Source #
Copy the value in a register to another one. Must work for all register classes.
regUsageOfInstr :: Platform -> Instr -> RegUsage Source #
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.
isJumpishInstr :: Instr -> Bool Source #
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.
isMetaInstr :: Instr -> Bool Source #