Safe Haskell | None |
---|---|
Language | GHC2021 |
Note [Native code generator] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
The native-code generator has machine-independent and machine-dependent modules.
This module (GHC.CmmToAsm) is the top-level machine-independent
module. Before entering machine-dependent land, we do some
machine-independent optimisations (defined below) on the
CmmStmts
s. (Which ideally would be folded into CmmOpt ...)
We convert to the machine-specific Instr
datatype with
cmmCodeGen
, assuming an infinite supply of registers. We then use
a (mostly) machine-independent register allocator to rejoin
reality. Obviously, regAlloc
has machine-specific helper
functions (see the used register allocator for details).
Finally, we order the basic blocks of the function so as to minimise the number of jumps between blocks, by utilising fallthrough wherever possible.
The machine-dependent bits are generally contained under GHCCmmToAsmArch/* and generally breaks down as follows:
- Regs: Everything about the target platform's machine registers (and immediate operands, and addresses, which tend to intermingle/interact with registers).
- Instr: Includes the
Instr
datatype plus a miscellany of other things (e.g.,targetDoubleSize
,smStablePtrTable
, ...) - CodeGen: is where
Cmm
stuff turns into machine instructions. - Ppr:
pprInstr
turns anInstr
into text (well, really aSDoc
).
The register allocators lives under GHC.CmmToAsm.Reg.*, there is both a Linear and a Graph based register allocator. Both of which have their own notes describing them. They are mostly platform independent but there are some platform specific files encoding architecture details under RegAllocatorArch.hs
- }
Synopsis
- nativeCodeGen :: Logger -> ToolSettings -> NCGConfig -> ModLocation -> Handle -> UniqSupply -> Stream IO RawCmmGroup a -> IO a
- cmmNativeGen :: forall statics instr jumpDest. (Instruction instr, OutputableP Platform statics, Outputable jumpDest) => Logger -> 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
- pprNatCmmDeclS :: NatCmmDecl statics instr -> SDoc
- pprNatCmmDeclH :: NatCmmDecl statics instr -> HDoc
- maxSpillSlots :: Int
- allocatableRegs :: [RealReg]
- ncgAllocMoreStack :: Int -> NatCmmDecl statics instr -> UniqSM (NatCmmDecl statics instr, [(BlockId, BlockId)])
- ncgMakeFarBranches :: Platform -> LabelMap RawCmmStatics -> [NatBasicBlock instr] -> UniqSM [NatBasicBlock instr]
- extractUnwindPoints :: [instr] -> [UnwindPoint]
- invertCondBranches :: Maybe CFG -> LabelMap RawCmmStatics -> [NatBasicBlock instr] -> [NatBasicBlock instr]
Documentation
nativeCodeGen :: Logger -> ToolSettings -> NCGConfig -> ModLocation -> Handle -> UniqSupply -> Stream IO RawCmmGroup a -> IO a Source #
Test-only exports: see #12744
:: forall statics instr jumpDest. (Instruction instr, OutputableP Platform statics, Outputable jumpDest) | |
=> Logger | |
-> 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 | |
|