Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- 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]
- data NatM_State = NatM_State {}
- mkNatM_State :: UniqSupply -> Int -> DynFlags -> Module -> ModLocation -> DwarfFiles -> LabelMap DebugBlock -> CFG -> NatM_State
- data NatM result
- initNat :: NatM_State -> NatM a -> (a, NatM_State)
- initConfig :: DynFlags -> NCGConfig
- addImportNat :: CLabel -> NatM ()
- addNodeBetweenNat :: BlockId -> BlockId -> BlockId -> NatM ()
- addImmediateSuccessorNat :: BlockId -> BlockId -> NatM ()
- updateCfgNat :: (CFG -> CFG) -> NatM ()
- getUniqueNat :: NatM Unique
- mapAccumLNat :: (acc -> x -> NatM (acc, y)) -> acc -> [x] -> NatM (acc, [y])
- setDeltaNat :: Int -> NatM ()
- getConfig :: NatM NCGConfig
- getPlatform :: NatM Platform
- getDeltaNat :: NatM Int
- getThisModuleNat :: NatM Module
- getBlockIdNat :: NatM BlockId
- getNewLabelNat :: NatM CLabel
- getNewRegNat :: Format -> NatM Reg
- getNewRegPairNat :: Format -> NatM (Reg, Reg)
- getPicBaseMaybeNat :: NatM (Maybe Reg)
- getPicBaseNat :: Format -> NatM Reg
- getDynFlags :: HasDynFlags m => m DynFlags
- getModLoc :: NatM ModLocation
- getFileId :: FastString -> NatM Int
- getDebugBlock :: Label -> NatM (Maybe DebugBlock)
- type DwarfFiles = UniqFM FastString (FastString, Int)
Documentation
data NcgImpl statics instr jumpDest Source #
NcgImpl | |
|
data NatM_State Source #
NatM_State | |
|
mkNatM_State :: UniqSupply -> Int -> DynFlags -> Module -> ModLocation -> DwarfFiles -> LabelMap DebugBlock -> CFG -> NatM_State Source #
Instances
Applicative NatM Source # | |
Functor NatM Source # | |
Monad NatM Source # | |
CmmMakeDynamicReferenceM NatM Source # | |
HasDynFlags NatM Source # | |
Defined in GHC.CmmToAsm.Monad | |
MonadUnique NatM Source # | |
Defined in GHC.CmmToAsm.Monad getUniqueSupplyM :: NatM UniqSupply Source # getUniqueM :: NatM Unique Source # getUniquesM :: NatM [Unique] Source # |
initNat :: NatM_State -> NatM a -> (a, NatM_State) Source #
initConfig :: DynFlags -> NCGConfig Source #
Initialize the native code generator configuration from the DynFlags
addImportNat :: CLabel -> NatM () Source #
addNodeBetweenNat :: BlockId -> BlockId -> BlockId -> NatM () Source #
Record that we added a block between from
and old
.
mapAccumLNat :: (acc -> x -> NatM (acc, y)) -> acc -> [x] -> NatM (acc, [y]) Source #
setDeltaNat :: Int -> NatM () Source #
getPlatform :: NatM Platform Source #
Get target platform from native code generator configuration
getDeltaNat :: NatM Int Source #
getDynFlags :: HasDynFlags m => m DynFlags Source #
getDebugBlock :: Label -> NatM (Maybe DebugBlock) Source #
type DwarfFiles = UniqFM FastString (FastString, Int) Source #