| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
SPARC.Instr
Synopsis
- data RI
 - riZero :: RI -> Bool
 - fpRelEA :: Int -> Reg -> Instr
 - moveSp :: Int -> Instr
 - isUnconditionalJump :: Instr -> Bool
 - data Instr
- = COMMENT FastString
 - | LDATA Section CmmStatics
 - | NEWBLOCK BlockId
 - | DELTA Int
 - | LD Format AddrMode Reg
 - | ST Format Reg AddrMode
 - | ADD Bool Bool Reg RI Reg
 - | SUB Bool Bool Reg RI Reg
 - | UMUL Bool Reg RI Reg
 - | SMUL Bool Reg RI Reg
 - | UDIV Bool Reg RI Reg
 - | SDIV Bool Reg RI Reg
 - | RDY Reg
 - | WRY Reg Reg
 - | AND Bool Reg RI Reg
 - | ANDN Bool Reg RI Reg
 - | OR Bool Reg RI Reg
 - | ORN Bool Reg RI Reg
 - | XOR Bool Reg RI Reg
 - | XNOR Bool Reg RI Reg
 - | SLL Reg RI Reg
 - | SRL Reg RI Reg
 - | SRA Reg RI Reg
 - | SETHI Imm Reg
 - | NOP
 - | FABS Format Reg Reg
 - | FADD Format Reg Reg Reg
 - | FCMP Bool Format Reg Reg
 - | FDIV Format Reg Reg Reg
 - | FMOV Format Reg Reg
 - | FMUL Format Reg Reg Reg
 - | FNEG Format Reg Reg
 - | FSQRT Format Reg Reg
 - | FSUB Format Reg Reg Reg
 - | FxTOy Format Format Reg Reg
 - | BI Cond Bool BlockId
 - | BF Cond Bool BlockId
 - | JMP AddrMode
 - | JMP_TBL AddrMode [Maybe BlockId] CLabel
 - | CALL (Either Imm Reg) Int Bool
 
 - maxSpillSlots :: DynFlags -> Int
 
Documentation
Check if a RI represents a zero value. - a literal zero - register %g0, which is always zero.
fpRelEA :: Int -> Reg -> Instr Source #
Calculate the effective address which would be used by the corresponding fpRel sequence.
isUnconditionalJump :: Instr -> Bool Source #
An instruction that will cause the one after it never to be exectuted
SPARC instruction set. Not complete. This is only the ones we need.
Constructors
| COMMENT FastString | |
| LDATA Section CmmStatics | |
| NEWBLOCK BlockId | |
| DELTA Int | |
| LD Format AddrMode Reg | |
| ST Format Reg AddrMode | |
| ADD Bool Bool Reg RI Reg | |
| SUB Bool Bool Reg RI Reg | |
| UMUL Bool Reg RI Reg | |
| SMUL Bool Reg RI Reg | |
| UDIV Bool Reg RI Reg | |
| SDIV Bool Reg RI Reg | |
| RDY Reg | |
| WRY Reg Reg | |
| AND Bool Reg RI Reg | |
| ANDN Bool Reg RI Reg | |
| OR Bool Reg RI Reg | |
| ORN Bool Reg RI Reg | |
| XOR Bool Reg RI Reg | |
| XNOR Bool Reg RI Reg | |
| SLL Reg RI Reg | |
| SRL Reg RI Reg | |
| SRA Reg RI Reg | |
| SETHI Imm Reg | |
| NOP | |
| FABS Format Reg Reg | |
| FADD Format Reg Reg Reg | |
| FCMP Bool Format Reg Reg | |
| FDIV Format Reg Reg Reg | |
| FMOV Format Reg Reg | |
| FMUL Format Reg Reg Reg | |
| FNEG Format Reg Reg | |
| FSQRT Format Reg Reg | |
| FSUB Format Reg Reg Reg | |
| FxTOy Format Format Reg Reg | |
| BI Cond Bool BlockId | |
| BF Cond Bool BlockId | |
| JMP AddrMode | |
| JMP_TBL AddrMode [Maybe BlockId] CLabel | |
| CALL (Either Imm Reg) Int Bool | 
Instances
| Outputable Instr Source # | |
| Instruction Instr Source # | instance for sparc instruction set  | 
Defined in SPARC.Instr Methods 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 #  | |
maxSpillSlots :: DynFlags -> Int Source #
The maximum number of spill slots available on the C stack. If we use up all of the slots, then we're screwed.
Why do we reserve 64 bytes, instead of using the whole thing?? -- BL 20090215