Safe Haskell | None |
---|---|
Language | Haskell2010 |
- archWordFormat :: Bool -> Format
- data RI
- data Instr
- = COMMENT FastString
- | LDATA Section CmmStatics
- | NEWBLOCK BlockId
- | DELTA Int
- | LD Format Reg AddrMode
- | LDFAR Format Reg AddrMode
- | LA Format Reg AddrMode
- | ST Format Reg AddrMode
- | STFAR Format Reg AddrMode
- | STU Format Reg AddrMode
- | LIS Reg Imm
- | LI Reg Imm
- | MR Reg Reg
- | CMP Format Reg RI
- | CMPL Format Reg RI
- | BCC Cond BlockId
- | BCCFAR Cond BlockId
- | JMP CLabel
- | MTCTR Reg
- | BCTR [Maybe BlockId] (Maybe CLabel)
- | BL CLabel [Reg]
- | BCTRL [Reg]
- | ADD Reg Reg RI
- | ADDC Reg Reg Reg
- | ADDE Reg Reg Reg
- | ADDI Reg Reg Imm
- | ADDIS Reg Reg Imm
- | SUBF Reg Reg Reg
- | SUBFC Reg Reg Reg
- | SUBFE Reg Reg Reg
- | MULLD Reg Reg RI
- | MULLW Reg Reg RI
- | DIVW Reg Reg Reg
- | DIVD Reg Reg Reg
- | DIVWU Reg Reg Reg
- | DIVDU Reg Reg Reg
- | MULLW_MayOflo Reg Reg Reg
- | MULLD_MayOflo Reg Reg Reg
- | AND Reg Reg RI
- | OR Reg Reg RI
- | ORIS Reg Reg Imm
- | XOR Reg Reg RI
- | XORIS Reg Reg Imm
- | EXTS 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
- | FADD Format Reg Reg Reg
- | FSUB Format Reg Reg Reg
- | FMUL Format Reg Reg Reg
- | FDIV Format Reg 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
- | FETCHTOC Reg CLabel
- | LWSYNC
- | NOP
- | UPDATE_SP Format Imm
- maxSpillSlots :: DynFlags -> Int
- allocMoreStack :: Platform -> Int -> NatCmmDecl statics Instr -> UniqSM (NatCmmDecl statics Instr)
- makeFarBranches :: BlockEnv CmmStatics -> [NatBasicBlock Instr] -> [NatBasicBlock Instr]
Documentation
archWordFormat :: Bool -> Format Source #
Instruction Instr # | Instruction instance for powerpc |
maxSpillSlots :: DynFlags -> Int Source #
The number of spill slots available without allocating more.
allocMoreStack :: Platform -> Int -> NatCmmDecl statics Instr -> UniqSM (NatCmmDecl statics Instr) Source #
makeFarBranches :: BlockEnv CmmStatics -> [NatBasicBlock Instr] -> [NatBasicBlock Instr] Source #