Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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.
We convert to the machine-specific Instr
datatype with
cmmCodeGen
, assuming an infinite supply of registers. We then use
a machine-independent register allocator (regAlloc
) to rejoin
reality. Obviously, regAlloc
has machine-specific helper
functions (see about RegAllocInfo below).
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 break down as follows:
- [MachRegs] Everything about the target platform's machine registers (and immediate operands, and addresses, which tend to intermingle/interact with registers).
- [MachInstrs] Includes the
Instr
datatype (possibly should have a module of its own), plus a miscellany of other things (e.g.,targetDoubleSize
,smStablePtrTable
, ...) - [MachCodeGen] is where
Cmm
stuff turns into machine instructions. - [PprMach]
pprInstr
turns anInstr
into text (well, really aSDoc
). - [RegAllocInfo] In the register allocator, we manipulate
MRegsState
s, which areBitSet
s, one bit per machine register. When we want to say something about a specific machine register (e.g., ``it gets clobbered by this instruction''), we set/unset its bit. Obviously, we do thisBitSet
thing for efficiency reasons.
The RegAllocInfo
module collects together the machine-specific
info needed to do register allocation.
- [RegisterAlloc] The (machine-independent) register allocator. -}
Synopsis
- nativeCodeGen :: forall a. 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 :: LabelMap RawCmmStatics -> [NatBasicBlock instr] -> [NatBasicBlock instr]
- extractUnwindPoints :: [instr] -> [UnwindPoint]
- invertCondBranches :: Maybe CFG -> LabelMap RawCmmStatics -> [NatBasicBlock instr] -> [NatBasicBlock instr]
Documentation
nativeCodeGen :: forall a. Logger -> ToolSettings -> NCGConfig -> ModLocation -> Handle -> UniqSupply -> Stream IO RawCmmGroup a -> IO a Source #
Test-only exports: see trac #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 | |
|