Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- archWordFormat :: Bool -> Format
- data RI
- data Instr
- = COMMENT FastString
- | LDATA Section CmmStatics
- | 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
- stackFrameHeaderSize :: DynFlags -> Int
- maxSpillSlots :: DynFlags -> Int
- allocMoreStack :: Platform -> Int -> NatCmmDecl statics Instr -> UniqSM (NatCmmDecl statics Instr, [(BlockId, BlockId)])
- makeFarBranches :: LabelMap CmmStatics -> [NatBasicBlock Instr] -> [NatBasicBlock Instr]
Documentation
archWordFormat :: Bool -> Format Source #
Instances
Outputable Instr # | |
Instruction Instr # | Instruction instance for powerpc |
Defined in PPC.Instr 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 :: DynFlags -> Reg -> Int -> Int -> Instr Source # mkLoadInstr :: DynFlags -> 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 # |
stackFrameHeaderSize :: DynFlags -> Int Source #
The size of a minimal stackframe header including minimal parameter save area.
maxSpillSlots :: DynFlags -> 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 CmmStatics -> [NatBasicBlock Instr] -> [NatBasicBlock Instr] Source #