#if !defined(GHC_LOADED_INTO_GHCI)
#endif
module AsmCodeGen (
nativeCodeGen
, cmmNativeGen
, NcgImpl(..)
, x86NcgImpl
) where
#include "HsVersions.h"
import GhcPrelude
import qualified X86.CodeGen
import qualified X86.Regs
import qualified X86.Instr
import qualified X86.Ppr
import qualified SPARC.CodeGen
import qualified SPARC.Regs
import qualified SPARC.Instr
import qualified SPARC.Ppr
import qualified SPARC.ShortcutJump
import qualified SPARC.CodeGen.Expand
import qualified PPC.CodeGen
import qualified PPC.Regs
import qualified PPC.RegInfo
import qualified PPC.Instr
import qualified PPC.Ppr
import RegAlloc.Liveness
import qualified RegAlloc.Linear.Main as Linear
import qualified GraphColor as Color
import qualified RegAlloc.Graph.Main as Color
import qualified RegAlloc.Graph.Stats as Color
import qualified RegAlloc.Graph.TrivColorable as Color
import AsmUtils
import TargetReg
import GHC.Platform
import BlockLayout
import Config
import Instruction
import PIC
import Reg
import NCGMonad
import CFG
import Dwarf
import Debug
import BlockId
import GHC.StgToCmm.CgUtils ( fixStgRegisters )
import Cmm
import CmmUtils
import Hoopl.Collections
import Hoopl.Label
import Hoopl.Block
import CmmOpt ( cmmMachOpFold )
import PprCmm
import CLabel
import UniqFM
import UniqSupply
import DynFlags
import Util
import BasicTypes ( Alignment )
import qualified Pretty
import BufWrite
import Outputable
import FastString
import UniqSet
import ErrUtils
import Module
import Stream (Stream)
import qualified Stream
import Data.List
import Data.Maybe
import Data.Ord ( comparing )
import Control.Exception
import Control.Monad
import System.IO
nativeCodeGen :: forall a . DynFlags -> Module -> ModLocation -> Handle -> UniqSupply
-> Stream IO RawCmmGroup a
-> IO a
nativeCodeGen dflags this_mod modLoc h us cmms
= let platform = targetPlatform dflags
nCG' :: ( Outputable statics, Outputable instr
, Outputable jumpDest, Instruction instr)
=> NcgImpl statics instr jumpDest -> IO a
nCG' ncgImpl = nativeCodeGen' dflags this_mod modLoc ncgImpl h us cmms
in case platformArch platform of
ArchX86 -> nCG' (x86NcgImpl dflags)
ArchX86_64 -> nCG' (x86_64NcgImpl dflags)
ArchPPC -> nCG' (ppcNcgImpl dflags)
ArchS390X -> panic "nativeCodeGen: No NCG for S390X"
ArchSPARC -> nCG' (sparcNcgImpl dflags)
ArchSPARC64 -> panic "nativeCodeGen: No NCG for SPARC64"
ArchARM {} -> panic "nativeCodeGen: No NCG for ARM"
ArchARM64 -> panic "nativeCodeGen: No NCG for ARM64"
ArchPPC_64 _ -> nCG' (ppcNcgImpl dflags)
ArchAlpha -> panic "nativeCodeGen: No NCG for Alpha"
ArchMipseb -> panic "nativeCodeGen: No NCG for mipseb"
ArchMipsel -> panic "nativeCodeGen: No NCG for mipsel"
ArchUnknown -> panic "nativeCodeGen: No NCG for unknown arch"
ArchJavaScript-> panic "nativeCodeGen: No NCG for JavaScript"
x86NcgImpl :: DynFlags -> NcgImpl (Alignment, CmmStatics)
X86.Instr.Instr X86.Instr.JumpDest
x86NcgImpl dflags
= (x86_64NcgImpl dflags)
x86_64NcgImpl :: DynFlags -> NcgImpl (Alignment, CmmStatics)
X86.Instr.Instr X86.Instr.JumpDest
x86_64NcgImpl dflags
= NcgImpl {
cmmTopCodeGen = X86.CodeGen.cmmTopCodeGen
,generateJumpTableForInstr = X86.CodeGen.generateJumpTableForInstr dflags
,getJumpDestBlockId = X86.Instr.getJumpDestBlockId
,canShortcut = X86.Instr.canShortcut
,shortcutStatics = X86.Instr.shortcutStatics
,shortcutJump = X86.Instr.shortcutJump
,pprNatCmmDecl = X86.Ppr.pprNatCmmDecl
,maxSpillSlots = X86.Instr.maxSpillSlots dflags
,allocatableRegs = X86.Regs.allocatableRegs platform
,ncgAllocMoreStack = X86.Instr.allocMoreStack platform
,ncgExpandTop = id
,ncgMakeFarBranches = const id
,extractUnwindPoints = X86.CodeGen.extractUnwindPoints
,invertCondBranches = X86.CodeGen.invertCondBranches
}
where platform = targetPlatform dflags
ppcNcgImpl :: DynFlags -> NcgImpl CmmStatics PPC.Instr.Instr PPC.RegInfo.JumpDest
ppcNcgImpl dflags
= NcgImpl {
cmmTopCodeGen = PPC.CodeGen.cmmTopCodeGen
,generateJumpTableForInstr = PPC.CodeGen.generateJumpTableForInstr dflags
,getJumpDestBlockId = PPC.RegInfo.getJumpDestBlockId
,canShortcut = PPC.RegInfo.canShortcut
,shortcutStatics = PPC.RegInfo.shortcutStatics
,shortcutJump = PPC.RegInfo.shortcutJump
,pprNatCmmDecl = PPC.Ppr.pprNatCmmDecl
,maxSpillSlots = PPC.Instr.maxSpillSlots dflags
,allocatableRegs = PPC.Regs.allocatableRegs platform
,ncgAllocMoreStack = PPC.Instr.allocMoreStack platform
,ncgExpandTop = id
,ncgMakeFarBranches = PPC.Instr.makeFarBranches
,extractUnwindPoints = const []
,invertCondBranches = \_ _ -> id
}
where platform = targetPlatform dflags
sparcNcgImpl :: DynFlags -> NcgImpl CmmStatics SPARC.Instr.Instr SPARC.ShortcutJump.JumpDest
sparcNcgImpl dflags
= NcgImpl {
cmmTopCodeGen = SPARC.CodeGen.cmmTopCodeGen
,generateJumpTableForInstr = SPARC.CodeGen.generateJumpTableForInstr dflags
,getJumpDestBlockId = SPARC.ShortcutJump.getJumpDestBlockId
,canShortcut = SPARC.ShortcutJump.canShortcut
,shortcutStatics = SPARC.ShortcutJump.shortcutStatics
,shortcutJump = SPARC.ShortcutJump.shortcutJump
,pprNatCmmDecl = SPARC.Ppr.pprNatCmmDecl
,maxSpillSlots = SPARC.Instr.maxSpillSlots dflags
,allocatableRegs = SPARC.Regs.allocatableRegs
,ncgAllocMoreStack = noAllocMoreStack
,ncgExpandTop = map SPARC.CodeGen.Expand.expandTop
,ncgMakeFarBranches = const id
,extractUnwindPoints = const []
,invertCondBranches = \_ _ -> id
}
noAllocMoreStack :: Int -> NatCmmDecl statics instr
-> UniqSM (NatCmmDecl statics instr, [(BlockId,BlockId)])
noAllocMoreStack amount _
= panic $ "Register allocator: out of stack slots (need " ++ show amount ++ ")\n"
++ " If you are trying to compile SHA1.hs from the crypto library then this\n"
++ " is a known limitation in the linear allocator.\n"
++ "\n"
++ " Try enabling the graph colouring allocator with -fregs-graph instead."
++ " You can still file a bug report if you like.\n"
data NativeGenAcc statics instr
= NGS { ngs_imports :: ![[CLabel]]
, ngs_natives :: ![[NatCmmDecl statics instr]]
, ngs_colorStats :: ![[Color.RegAllocStats statics instr]]
, ngs_linearStats :: ![[Linear.RegAllocStats]]
, ngs_labels :: ![Label]
, ngs_debug :: ![DebugBlock]
, ngs_dwarfFiles :: !DwarfFiles
, ngs_unwinds :: !(LabelMap [UnwindPoint])
}
nativeCodeGen' :: (Outputable statics, Outputable instr,Outputable jumpDest,
Instruction instr)
=> DynFlags
-> Module -> ModLocation
-> NcgImpl statics instr jumpDest
-> Handle
-> UniqSupply
-> Stream IO RawCmmGroup a
-> IO a
nativeCodeGen' dflags this_mod modLoc ncgImpl h us cmms
= do
bufh <- newBufHandle h
let ngs0 = NGS [] [] [] [] [] [] emptyUFM mapEmpty
(ngs, us', a) <- cmmNativeGenStream dflags this_mod modLoc ncgImpl bufh us
cmms ngs0
_ <- finishNativeGen dflags modLoc bufh us' ngs
return a
finishNativeGen :: Instruction instr
=> DynFlags
-> ModLocation
-> BufHandle
-> UniqSupply
-> NativeGenAcc statics instr
-> IO UniqSupply
finishNativeGen dflags modLoc bufh@(BufHandle _ _ h) us ngs
= withTimingSilent dflags (text "NCG") (`seq` ()) $ do
let emitDw = debugLevel dflags > 0
us' <- if not emitDw then return us else do
(dwarf, us') <- dwarfGen dflags modLoc us (ngs_debug ngs)
emitNativeCode dflags bufh dwarf
return us'
bFlush bufh
let stats = concat (ngs_colorStats ngs)
unless (null stats) $ do
let graphGlobal
= foldl' Color.union Color.initGraph
$ [ Color.raGraph stat
| stat@Color.RegAllocStatsStart{} <- stats]
dump_stats (Color.pprStats stats graphGlobal)
let platform = targetPlatform dflags
dumpIfSet_dyn dflags
Opt_D_dump_asm_conflicts "Register conflict graph"
$ Color.dotGraph
(targetRegDotColor platform)
(Color.trivColorable platform
(targetVirtualRegSqueeze platform)
(targetRealRegSqueeze platform))
$ graphGlobal
let linearStats = concat (ngs_linearStats ngs)
unless (null linearStats) $
dump_stats (Linear.pprStats (concat (ngs_natives ngs)) linearStats)
printSDocLn Pretty.LeftMode dflags h (mkCodeStyle AsmStyle)
$ makeImportsDoc dflags (concat (ngs_imports ngs))
return us'
where
dump_stats = dumpSDoc dflags alwaysQualify Opt_D_dump_asm_stats "NCG stats"
cmmNativeGenStream :: (Outputable statics, Outputable instr
,Outputable jumpDest, Instruction instr)
=> DynFlags
-> Module -> ModLocation
-> NcgImpl statics instr jumpDest
-> BufHandle
-> UniqSupply
-> Stream IO RawCmmGroup a
-> NativeGenAcc statics instr
-> IO (NativeGenAcc statics instr, UniqSupply, a)
cmmNativeGenStream dflags this_mod modLoc ncgImpl h us cmm_stream ngs
= do r <- Stream.runStream cmm_stream
case r of
Left a ->
return (ngs { ngs_imports = reverse $ ngs_imports ngs
, ngs_natives = reverse $ ngs_natives ngs
, ngs_colorStats = reverse $ ngs_colorStats ngs
, ngs_linearStats = reverse $ ngs_linearStats ngs
},
us,
a)
Right (cmms, cmm_stream') -> do
(us', ngs'') <-
withTimingSilent
dflags
ncglabel (\(a, b) -> a `seq` b `seq` ()) $ do
let debugFlag = debugLevel dflags > 0
!ndbgs | debugFlag = cmmDebugGen modLoc cmms
| otherwise = []
dbgMap = debugToMap ndbgs
(ngs',us') <- cmmNativeGens dflags this_mod modLoc ncgImpl h
dbgMap us cmms ngs 0
let !ldbgs = cmmDebugLink (ngs_labels ngs') (ngs_unwinds ngs') ndbgs
unless (null ldbgs) $
dumpIfSet_dyn dflags Opt_D_dump_debug "Debug Infos"
(vcat $ map ppr ldbgs)
let ngs'' = ngs' { ngs_debug = ngs_debug ngs' ++ ldbgs, ngs_labels = [] }
return (us', ngs'')
cmmNativeGenStream dflags this_mod modLoc ncgImpl h us'
cmm_stream' ngs''
where ncglabel = text "NCG"
cmmNativeGens :: forall statics instr jumpDest.
(Outputable statics, Outputable instr
,Outputable jumpDest, Instruction instr)
=> DynFlags
-> Module -> ModLocation
-> NcgImpl statics instr jumpDest
-> BufHandle
-> LabelMap DebugBlock
-> UniqSupply
-> [RawCmmDecl]
-> NativeGenAcc statics instr
-> Int
-> IO (NativeGenAcc statics instr, UniqSupply)
cmmNativeGens dflags this_mod modLoc ncgImpl h dbgMap = go
where
go :: UniqSupply -> [RawCmmDecl]
-> NativeGenAcc statics instr -> Int
-> IO (NativeGenAcc statics instr, UniqSupply)
go us [] ngs !_ =
return (ngs, us)
go us (cmm : cmms) ngs count = do
let fileIds = ngs_dwarfFiles ngs
(us', fileIds', native, imports, colorStats, linearStats, unwinds)
<-
cmmNativeGen dflags this_mod modLoc ncgImpl us fileIds dbgMap
cmm count
let newFileIds = sortBy (comparing snd) $
nonDetEltsUFM $ fileIds' `minusUFM` fileIds
pprDecl (f,n) = text "\t.file " <> ppr n <+>
pprFilePathString (unpackFS f)
emitNativeCode dflags h $ vcat $
map pprDecl newFileIds ++
map (pprNatCmmDecl ncgImpl) native
evaluate $ seqList (showSDoc dflags $ vcat $ map ppr imports) ()
let !labels' = if debugLevel dflags > 0
then cmmDebugLabels isMetaInstr native else []
!natives' = if dopt Opt_D_dump_asm_stats dflags
then native : ngs_natives ngs else []
mCon = maybe id (:)
ngs' = ngs{ ngs_imports = imports : ngs_imports ngs
, ngs_natives = natives'
, ngs_colorStats = colorStats `mCon` ngs_colorStats ngs
, ngs_linearStats = linearStats `mCon` ngs_linearStats ngs
, ngs_labels = ngs_labels ngs ++ labels'
, ngs_dwarfFiles = fileIds'
, ngs_unwinds = ngs_unwinds ngs `mapUnion` unwinds
}
go us' cmms ngs' (count + 1)
emitNativeCode :: DynFlags -> BufHandle -> SDoc -> IO ()
emitNativeCode dflags h sdoc = do
bufLeftRenderSDoc dflags h
(mkCodeStyle AsmStyle) sdoc
dumpIfSet_dyn dflags
Opt_D_dump_asm "Asm code"
sdoc
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 [Color.RegAllocStats statics instr]
, Maybe [Linear.RegAllocStats]
, LabelMap [UnwindPoint]
)
cmmNativeGen dflags this_mod modLoc ncgImpl us fileIds dbgMap cmm count
= do
let platform = targetPlatform dflags
let proc_name = case cmm of
(CmmProc _ entry_label _ _) -> ppr entry_label
_ -> text "DataChunk"
let fixed_cmm =
fixStgRegisters dflags cmm
let (opt_cmm, imports) =
cmmToCmm dflags this_mod fixed_cmm
dumpIfSet_dyn dflags
Opt_D_dump_opt_cmm "Optimised Cmm"
(pprCmmGroup [opt_cmm])
let cmmCfg =
getCfgProc (cfgWeightInfo dflags) opt_cmm
let ((native, lastMinuteImports, fileIds', nativeCfgWeights), usGen) =
initUs us $ genMachCode dflags this_mod modLoc
(cmmTopCodeGen ncgImpl)
fileIds dbgMap opt_cmm cmmCfg
dumpIfSet_dyn dflags
Opt_D_dump_asm_native "Native code"
(vcat $ map (pprNatCmmDecl ncgImpl) native)
maybeDumpCfg dflags (Just nativeCfgWeights) "CFG Weights - Native" proc_name
let livenessCfg = if (backendMaintainsCfg dflags)
then Just nativeCfgWeights
else Nothing
let (withLiveness, usLive) =
initUs usGen
$ mapM (cmmTopLiveness livenessCfg platform) native
dumpIfSet_dyn dflags
Opt_D_dump_asm_liveness "Liveness annotations added"
(vcat $ map ppr withLiveness)
(alloced, usAlloc, ppr_raStatsColor, ppr_raStatsLinear, raStats, stack_updt_blks) <-
if ( gopt Opt_RegsGraph dflags
|| gopt Opt_RegsIterative dflags )
then do
let (alloc_regs :: UniqFM (UniqSet RealReg))
= foldr (\r -> plusUFM_C unionUniqSets
$ unitUFM (targetClassOfRealReg platform r) (unitUniqSet r))
emptyUFM
$ allocatableRegs ncgImpl
let ((alloced, maybe_more_stack, regAllocStats), usAlloc)
=
initUs usLive
$ Color.regAlloc
dflags
alloc_regs
(mkUniqSet [0 .. maxSpillSlots ncgImpl])
(maxSpillSlots ncgImpl)
withLiveness
livenessCfg
let ((alloced', stack_updt_blks), usAlloc')
= initUs usAlloc $
case maybe_more_stack of
Nothing -> return (alloced, [])
Just amount -> do
(alloced',stack_updt_blks) <- unzip <$>
(mapM ((ncgAllocMoreStack ncgImpl) amount) alloced)
return (alloced', concat stack_updt_blks )
dumpIfSet_dyn dflags
Opt_D_dump_asm_regalloc "Registers allocated"
(vcat $ map (pprNatCmmDecl ncgImpl) alloced)
dumpIfSet_dyn dflags
Opt_D_dump_asm_regalloc_stages "Build/spill stages"
(vcat $ map (\(stage, stats)
-> text "# --------------------------"
$$ text "# cmm " <> int count <> text " Stage " <> int stage
$$ ppr stats)
$ zip [0..] regAllocStats)
let mPprStats =
if dopt Opt_D_dump_asm_stats dflags
then Just regAllocStats else Nothing
mPprStats `seq` return ()
return ( alloced', usAlloc'
, mPprStats
, Nothing
, [], stack_updt_blks)
else do
let reg_alloc proc = do
(alloced, maybe_more_stack, ra_stats) <-
Linear.regAlloc dflags proc
case maybe_more_stack of
Nothing -> return ( alloced, ra_stats, [] )
Just amount -> do
(alloced',stack_updt_blks) <-
ncgAllocMoreStack ncgImpl amount alloced
return (alloced', ra_stats, stack_updt_blks )
let ((alloced, regAllocStats, stack_updt_blks), usAlloc)
=
initUs usLive
$ liftM unzip3
$ mapM reg_alloc withLiveness
dumpIfSet_dyn dflags
Opt_D_dump_asm_regalloc "Registers allocated"
(vcat $ map (pprNatCmmDecl ncgImpl) alloced)
let mPprStats =
if dopt Opt_D_dump_asm_stats dflags
then Just (catMaybes regAllocStats) else Nothing
mPprStats `seq` return ()
return ( alloced, usAlloc
, Nothing
, mPprStats, (catMaybes regAllocStats)
, concat stack_updt_blks )
let cfgRegAllocUpdates :: [(BlockId,BlockId,BlockId)]
cfgRegAllocUpdates = (concatMap Linear.ra_fixupList raStats)
let cfgWithFixupBlks =
(\cfg -> addNodesBetween cfg cfgRegAllocUpdates) <$> livenessCfg
let postRegCFG =
pure (foldl' (\m (from,to) -> addImmediateSuccessor from to m ))
<*> cfgWithFixupBlks
<*> pure stack_updt_blks
let tabled =
generateJumpTables ncgImpl alloced
when (not $ null nativeCfgWeights) $ dumpIfSet_dyn dflags
Opt_D_dump_cfg_weights "CFG Update information"
( text "stack:" <+> ppr stack_updt_blks $$
text "linearAlloc:" <+> ppr cfgRegAllocUpdates )
let (shorted, postShortCFG) =
shortcutBranches dflags ncgImpl tabled postRegCFG
let optimizedCFG :: Maybe CFG
optimizedCFG =
optimizeCFG (cfgWeightInfo dflags) cmm <$!> postShortCFG
maybeDumpCfg dflags optimizedCFG "CFG Weights - Final" proc_name
let getBlks (CmmProc _info _lbl _live (ListGraph blocks)) = blocks
getBlks _ = []
when ( backendMaintainsCfg dflags &&
(gopt Opt_DoAsmLinting dflags || debugIsOn )) $ do
let blocks = concatMap getBlks shorted
let labels = setFromList $ fmap blockId blocks :: LabelSet
let cfg = fromJust optimizedCFG
return $! seq (sanityCheckCfg cfg labels $
text "cfg not in lockstep") ()
let sequenced :: [NatCmmDecl statics instr]
sequenced =
checkLayout shorted $
map (BlockLayout.sequenceTop
dflags
ncgImpl optimizedCFG)
shorted
let branchOpt :: [NatCmmDecl statics instr]
branchOpt =
map invert sequenced
where
invertConds :: LabelMap CmmStatics -> [NatBasicBlock instr]
-> [NatBasicBlock instr]
invertConds = invertCondBranches ncgImpl optimizedCFG
invert top@CmmData {} = top
invert (CmmProc info lbl live (ListGraph blocks)) =
CmmProc info lbl live (ListGraph $ invertConds info blocks)
let expanded =
ncgExpandTop ncgImpl branchOpt
dumpIfSet_dyn dflags
Opt_D_dump_asm_expanded "Synthetic instructions expanded"
(vcat $ map (pprNatCmmDecl ncgImpl) expanded)
let unwinds :: BlockMap [UnwindPoint]
unwinds =
foldl' addUnwind mapEmpty expanded
where
addUnwind acc proc =
acc `mapUnion` computeUnwinding dflags ncgImpl proc
return ( usAlloc
, fileIds'
, expanded
, lastMinuteImports ++ imports
, ppr_raStatsColor
, ppr_raStatsLinear
, unwinds )
maybeDumpCfg :: DynFlags -> Maybe CFG -> String -> SDoc -> IO ()
maybeDumpCfg _dflags Nothing _ _ = return ()
maybeDumpCfg dflags (Just cfg) msg proc_name
| null cfg = return ()
| otherwise
= dumpIfSet_dyn
dflags Opt_D_dump_cfg_weights msg
(proc_name <> char ':' $$ pprEdgeWeights cfg)
checkLayout :: [NatCmmDecl statics instr] -> [NatCmmDecl statics instr]
-> [NatCmmDecl statics instr]
checkLayout procsUnsequenced procsSequenced =
ASSERT2(setNull diff,
ppr "Block sequencing dropped blocks:" <> ppr diff)
procsSequenced
where
blocks1 = foldl' (setUnion) setEmpty $
map getBlockIds procsUnsequenced :: LabelSet
blocks2 = foldl' (setUnion) setEmpty $
map getBlockIds procsSequenced
diff = setDifference blocks1 blocks2
getBlockIds (CmmData _ _) = setEmpty
getBlockIds (CmmProc _ _ _ (ListGraph blocks)) =
setFromList $ map blockId blocks
computeUnwinding :: Instruction instr
=> DynFlags -> NcgImpl statics instr jumpDest
-> NatCmmDecl statics instr
-> LabelMap [UnwindPoint]
computeUnwinding dflags _ _
| debugLevel dflags == 0 = mapEmpty
computeUnwinding _ _ (CmmData _ _) = mapEmpty
computeUnwinding _ ncgImpl (CmmProc _ _ _ (ListGraph blks)) =
mapFromList [ (blk_lbl, extractUnwindPoints ncgImpl instrs)
| BasicBlock blk_lbl instrs <- blks ]
makeImportsDoc :: DynFlags -> [CLabel] -> SDoc
makeImportsDoc dflags imports
= dyld_stubs imports
$$
(if platformHasSubsectionsViaSymbols platform
then text ".subsections_via_symbols"
else Outputable.empty)
$$
(if platformHasGnuNonexecStack platform
then text ".section .note.GNU-stack,\"\"," <> sectionType "progbits"
else Outputable.empty)
$$
(if platformHasIdentDirective platform
then let compilerIdent = text "GHC" <+> text cProjectVersion
in text ".ident" <+> doubleQuotes compilerIdent
else Outputable.empty)
where
platform = targetPlatform dflags
arch = platformArch platform
os = platformOS platform
dyld_stubs :: [CLabel] -> SDoc
dyld_stubs imps
| needImportedSymbols dflags arch os
= vcat $
(pprGotDeclaration dflags arch os :) $
map ( pprImportedSymbol dflags platform . fst . head) $
groupBy (\(_,a) (_,b) -> a == b) $
sortBy (\(_,a) (_,b) -> compare a b) $
map doPpr $
imps
| otherwise
= Outputable.empty
doPpr lbl = (lbl, renderWithStyle dflags (pprCLabel dflags lbl) astyle)
astyle = mkCodeStyle AsmStyle
generateJumpTables
:: NcgImpl statics instr jumpDest
-> [NatCmmDecl statics instr] -> [NatCmmDecl statics instr]
generateJumpTables ncgImpl xs = concatMap f xs
where f p@(CmmProc _ _ _ (ListGraph xs)) = p : concatMap g xs
f p = [p]
g (BasicBlock _ xs) = catMaybes (map (generateJumpTableForInstr ncgImpl) xs)
shortcutBranches
:: forall statics instr jumpDest. (Outputable jumpDest) => DynFlags
-> NcgImpl statics instr jumpDest
-> [NatCmmDecl statics instr]
-> Maybe CFG
-> ([NatCmmDecl statics instr],Maybe CFG)
shortcutBranches dflags ncgImpl tops weights
| gopt Opt_AsmShortcutting dflags
= ( map (apply_mapping ncgImpl mapping) tops'
, shortcutWeightMap mappingBid <$!> weights )
| otherwise
= (tops, weights)
where
(tops', mappings) = mapAndUnzip (build_mapping ncgImpl) tops
mapping = mapUnions mappings :: LabelMap jumpDest
mappingBid = fmap (getJumpDestBlockId ncgImpl) mapping
build_mapping :: forall instr t d statics jumpDest.
NcgImpl statics instr jumpDest
-> GenCmmDecl d (LabelMap t) (ListGraph instr)
-> (GenCmmDecl d (LabelMap t) (ListGraph instr)
,LabelMap jumpDest)
build_mapping _ top@(CmmData _ _) = (top, mapEmpty)
build_mapping _ (CmmProc info lbl live (ListGraph []))
= (CmmProc info lbl live (ListGraph []), mapEmpty)
build_mapping ncgImpl (CmmProc info lbl live (ListGraph (head:blocks)))
= (CmmProc info lbl live (ListGraph (head:others)), mapping)
where
shortcut_blocks :: [(BlockId, jumpDest)]
(_, shortcut_blocks, others) =
foldl' split (setEmpty :: LabelSet, [], []) blocks
split (s, shortcut_blocks, others) b@(BasicBlock id [insn])
| Just jd <- canShortcut ncgImpl insn
, Just dest <- getJumpDestBlockId ncgImpl jd
, not (has_info id)
, (setMember dest s) || dest == id
= (s, shortcut_blocks, b : others)
split (s, shortcut_blocks, others) (BasicBlock id [insn])
| Just dest <- canShortcut ncgImpl insn
, not (has_info id)
= (setInsert id s, (id,dest) : shortcut_blocks, others)
split (s, shortcut_blocks, others) other = (s, shortcut_blocks, other : others)
has_info l = mapMember l info
mapping = mapFromList shortcut_blocks
apply_mapping :: NcgImpl statics instr jumpDest
-> LabelMap jumpDest
-> GenCmmDecl statics h (ListGraph instr)
-> GenCmmDecl statics h (ListGraph instr)
apply_mapping ncgImpl ufm (CmmData sec statics)
= CmmData sec (shortcutStatics ncgImpl (\bid -> mapLookup bid ufm) statics)
apply_mapping ncgImpl ufm (CmmProc info lbl live (ListGraph blocks))
= CmmProc info lbl live (ListGraph $ map short_bb blocks)
where
short_bb (BasicBlock id insns) = BasicBlock id $! map short_insn insns
short_insn i = shortcutJump ncgImpl (\bid -> mapLookup bid ufm) i
genMachCode
:: DynFlags
-> Module -> ModLocation
-> (RawCmmDecl -> NatM [NatCmmDecl statics instr])
-> DwarfFiles
-> LabelMap DebugBlock
-> RawCmmDecl
-> CFG
-> UniqSM
( [NatCmmDecl statics instr]
, [CLabel]
, DwarfFiles
, CFG
)
genMachCode dflags this_mod modLoc cmmTopCodeGen fileIds dbgMap cmm_top cmm_cfg
= do { initial_us <- getUniqueSupplyM
; let initial_st = mkNatM_State initial_us 0 dflags this_mod
modLoc fileIds dbgMap cmm_cfg
(new_tops, final_st) = initNat initial_st (cmmTopCodeGen cmm_top)
final_delta = natm_delta final_st
final_imports = natm_imports final_st
final_cfg = natm_cfg final_st
; if final_delta == 0
then return (new_tops, final_imports
, natm_fileid final_st, final_cfg)
else pprPanic "genMachCode: nonzero final delta" (int final_delta)
}
cmmToCmm :: DynFlags -> Module -> RawCmmDecl -> (RawCmmDecl, [CLabel])
cmmToCmm _ _ top@(CmmData _ _) = (top, [])
cmmToCmm dflags this_mod (CmmProc info lbl live graph)
= runCmmOpt dflags this_mod $
do blocks' <- mapM cmmBlockConFold (toBlockList graph)
return $ CmmProc info lbl live (ofBlockList (g_entry graph) blocks')
#if !defined(GHC_LOADED_INTO_GHCI)
type OptMResult a = (# a, [CLabel] #)
pattern OptMResult :: a -> b -> (# a, b #)
pattern OptMResult x y = (# x, y #)
#else
data OptMResult a = OptMResult !a ![CLabel] deriving (Functor)
#endif
newtype CmmOptM a = CmmOptM (DynFlags -> Module -> [CLabel] -> OptMResult a)
deriving (Functor)
instance Applicative CmmOptM where
pure x = CmmOptM $ \_ _ imports -> OptMResult x imports
(<*>) = ap
instance Monad CmmOptM where
(CmmOptM f) >>= g =
CmmOptM $ \dflags this_mod imports0 ->
case f dflags this_mod imports0 of
OptMResult x imports1 ->
case g x of
CmmOptM g' -> g' dflags this_mod imports1
instance CmmMakeDynamicReferenceM CmmOptM where
addImport = addImportCmmOpt
getThisModule = CmmOptM $ \_ this_mod imports -> OptMResult this_mod imports
addImportCmmOpt :: CLabel -> CmmOptM ()
addImportCmmOpt lbl = CmmOptM $ \_ _ imports -> OptMResult () (lbl:imports)
instance HasDynFlags CmmOptM where
getDynFlags = CmmOptM $ \dflags _ imports -> OptMResult dflags imports
runCmmOpt :: DynFlags -> Module -> CmmOptM a -> (a, [CLabel])
runCmmOpt dflags this_mod (CmmOptM f) =
case f dflags this_mod [] of
OptMResult result imports -> (result, imports)
cmmBlockConFold :: CmmBlock -> CmmOptM CmmBlock
cmmBlockConFold block = do
let (entry, middle, last) = blockSplit block
stmts = blockToList middle
stmts' <- mapM cmmStmtConFold stmts
last' <- cmmStmtConFold last
return $ blockJoin entry (blockFromList stmts') last'
cmmStmtConFold :: CmmNode e x -> CmmOptM (CmmNode e x)
cmmStmtConFold stmt
= case stmt of
CmmAssign reg src
-> do src' <- cmmExprConFold DataReference src
return $ case src' of
CmmReg reg' | reg == reg' -> CmmComment (fsLit "nop")
new_src -> CmmAssign reg new_src
CmmStore addr src
-> do addr' <- cmmExprConFold DataReference addr
src' <- cmmExprConFold DataReference src
return $ CmmStore addr' src'
CmmCall { cml_target = addr }
-> do addr' <- cmmExprConFold JumpReference addr
return $ stmt { cml_target = addr' }
CmmUnsafeForeignCall target regs args
-> do target' <- case target of
ForeignTarget e conv -> do
e' <- cmmExprConFold CallReference e
return $ ForeignTarget e' conv
PrimTarget _ ->
return target
args' <- mapM (cmmExprConFold DataReference) args
return $ CmmUnsafeForeignCall target' regs args'
CmmCondBranch test true false likely
-> do test' <- cmmExprConFold DataReference test
return $ case test' of
CmmLit (CmmInt 0 _) -> CmmBranch false
CmmLit (CmmInt _ _) -> CmmBranch true
_other -> CmmCondBranch test' true false likely
CmmSwitch expr ids
-> do expr' <- cmmExprConFold DataReference expr
return $ CmmSwitch expr' ids
other
-> return other
cmmExprConFold :: ReferenceKind -> CmmExpr -> CmmOptM CmmExpr
cmmExprConFold referenceKind expr = do
dflags <- getDynFlags
let expr' = if optLevel dflags >= 1
then expr
else cmmExprCon dflags expr
cmmExprNative referenceKind expr'
cmmExprCon :: DynFlags -> CmmExpr -> CmmExpr
cmmExprCon dflags (CmmLoad addr rep) = CmmLoad (cmmExprCon dflags addr) rep
cmmExprCon dflags (CmmMachOp mop args)
= cmmMachOpFold dflags mop (map (cmmExprCon dflags) args)
cmmExprCon _ other = other
cmmExprNative :: ReferenceKind -> CmmExpr -> CmmOptM CmmExpr
cmmExprNative referenceKind expr = do
dflags <- getDynFlags
let platform = targetPlatform dflags
arch = platformArch platform
case expr of
CmmLoad addr rep
-> do addr' <- cmmExprNative DataReference addr
return $ CmmLoad addr' rep
CmmMachOp mop args
-> do args' <- mapM (cmmExprNative DataReference) args
return $ CmmMachOp mop args'
CmmLit (CmmBlock id)
-> cmmExprNative referenceKind (CmmLit (CmmLabel (infoTblLbl id)))
CmmLit (CmmLabel lbl)
-> do
cmmMakeDynamicReference dflags referenceKind lbl
CmmLit (CmmLabelOff lbl off)
-> do
dynRef <- cmmMakeDynamicReference dflags referenceKind lbl
return $ cmmMachOpFold dflags (MO_Add (wordWidth dflags)) [
dynRef,
(CmmLit $ CmmInt (fromIntegral off) (wordWidth dflags))
]
CmmReg (CmmGlobal EagerBlackholeInfo)
| arch == ArchPPC && not (positionIndependent dflags)
-> cmmExprNative referenceKind $
CmmLit (CmmLabel (mkCmmCodeLabel rtsUnitId (fsLit "__stg_EAGER_BLACKHOLE_info")))
CmmReg (CmmGlobal GCEnter1)
| arch == ArchPPC && not (positionIndependent dflags)
-> cmmExprNative referenceKind $
CmmLit (CmmLabel (mkCmmCodeLabel rtsUnitId (fsLit "__stg_gc_enter_1")))
CmmReg (CmmGlobal GCFun)
| arch == ArchPPC && not (positionIndependent dflags)
-> cmmExprNative referenceKind $
CmmLit (CmmLabel (mkCmmCodeLabel rtsUnitId (fsLit "__stg_gc_fun")))
other
-> return other