Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- nativeCodeGen :: forall a. DynFlags -> Module -> ModLocation -> Handle -> UniqSupply -> Stream IO RawCmmGroup a -> IO a
- cmmNativeGen :: forall statics instr jumpDest. (Instruction instr, Outputable statics, Outputable instr, Outputable jumpDest) => DynFlags -> Module -> ModLocation -> NcgImpl statics instr jumpDest -> UniqSupply -> DwarfFiles -> LabelMap DebugBlock -> RawCmmDecl -> Int -> IO (UniqSupply, DwarfFiles, [NatCmmDecl statics instr], [CLabel], Maybe [RegAllocStats statics instr], Maybe [RegAllocStats], LabelMap [UnwindPoint])
- data NcgImpl statics instr jumpDest = NcgImpl {
- ncgConfig :: !NCGConfig
- cmmTopCodeGen :: RawCmmDecl -> NatM [NatCmmDecl statics instr]
- generateJumpTableForInstr :: instr -> Maybe (NatCmmDecl statics instr)
- getJumpDestBlockId :: jumpDest -> Maybe BlockId
- canShortcut :: instr -> Maybe jumpDest
- shortcutStatics :: (BlockId -> Maybe jumpDest) -> statics -> statics
- shortcutJump :: (BlockId -> Maybe jumpDest) -> instr -> instr
- pprNatCmmDecl :: NatCmmDecl statics instr -> SDoc
- maxSpillSlots :: Int
- allocatableRegs :: [RealReg]
- ncgExpandTop :: [NatCmmDecl statics instr] -> [NatCmmDecl statics instr]
- ncgAllocMoreStack :: Int -> NatCmmDecl statics instr -> UniqSM (NatCmmDecl statics instr, [(BlockId, BlockId)])
- ncgMakeFarBranches :: LabelMap RawCmmStatics -> [NatBasicBlock instr] -> [NatBasicBlock instr]
- extractUnwindPoints :: [instr] -> [UnwindPoint]
- invertCondBranches :: Maybe CFG -> LabelMap RawCmmStatics -> [NatBasicBlock instr] -> [NatBasicBlock instr]
- x86NcgImpl :: NCGConfig -> NcgImpl (Alignment, RawCmmStatics) Instr JumpDest
Module entry point
nativeCodeGen :: forall a. DynFlags -> Module -> ModLocation -> Handle -> UniqSupply -> Stream IO RawCmmGroup a -> IO a Source #
Test-only exports: see trac #12744
:: forall statics instr jumpDest. (Instruction instr, Outputable statics, Outputable instr, Outputable jumpDest) | |
=> DynFlags | |
-> Module | |
-> ModLocation | |
-> NcgImpl statics instr jumpDest | |
-> UniqSupply | |
-> DwarfFiles | |
-> LabelMap DebugBlock | |
-> RawCmmDecl | the cmm to generate code for |
-> Int | sequence number of this top thing |
-> IO (UniqSupply, DwarfFiles, [NatCmmDecl statics instr], [CLabel], Maybe [RegAllocStats statics instr], Maybe [RegAllocStats], LabelMap [UnwindPoint]) |
Complete native code generation phase for a single top-level chunk of Cmm. Dumping the output of each stage along the way. Global conflict graph and NGC stats
data NcgImpl statics instr jumpDest Source #
NcgImpl | |
|
x86NcgImpl :: NCGConfig -> NcgImpl (Alignment, RawCmmStatics) Instr JumpDest Source #