diff options
author | Simon Peyton Jones <simonpj@microsoft.com> | 2012-06-13 17:26:56 +0100 |
---|---|---|
committer | Simon Peyton Jones <simonpj@microsoft.com> | 2012-06-13 17:26:56 +0100 |
commit | 1e9a2d34ae6996b6872ee4cc87bc8218360fcaf9 (patch) | |
tree | 1c10162c5b8f6d83702cc3c80fb7418346318790 | |
parent | 5a8ac0f823c151c062a3f1903574030423bb255c (diff) | |
parent | 2b015ce92253f6c64230b80603091c1fa426cf2e (diff) | |
download | haskell-1e9a2d34ae6996b6872ee4cc87bc8218360fcaf9.tar.gz |
Merge branch 'master' of http://darcs.haskell.org/ghc
-rw-r--r-- | compiler/cmm/CLabel.hs | 102 | ||||
-rw-r--r-- | compiler/cmm/CmmBuildInfoTables.hs | 20 | ||||
-rw-r--r-- | compiler/cmm/CmmInfo.hs | 2 | ||||
-rw-r--r-- | compiler/cmm/CmmPipeline.hs | 4 | ||||
-rw-r--r-- | compiler/codeGen/StgCmmBind.hs | 10 | ||||
-rw-r--r-- | compiler/codeGen/StgCmmClosure.hs | 21 | ||||
-rw-r--r-- | compiler/codeGen/StgCmmHeap.hs | 9 | ||||
-rw-r--r-- | compiler/codeGen/StgCmmLayout.hs | 6 | ||||
-rw-r--r-- | compiler/codeGen/StgCmmTicky.hs | 3 | ||||
-rw-r--r-- | compiler/nativeGen/AsmCodeGen.lhs | 2 | ||||
-rw-r--r-- | compiler/nativeGen/RegAlloc/Graph/Main.hs | 4 | ||||
-rw-r--r-- | compiler/nativeGen/RegAlloc/Graph/SpillCost.hs | 6 | ||||
-rw-r--r-- | compiler/nativeGen/RegAlloc/Liveness.hs | 9 |
13 files changed, 90 insertions, 108 deletions
diff --git a/compiler/cmm/CLabel.hs b/compiler/cmm/CLabel.hs index 20cd584065..6ffbbc774d 100644 --- a/compiler/cmm/CLabel.hs +++ b/compiler/cmm/CLabel.hs @@ -252,8 +252,8 @@ data ForeignLabelSource -- We can't make a Show instance for CLabel because lots of its components don't have instances. -- The regular Outputable instance only shows the label name, and not its other info. -- -pprDebugCLabel :: Platform -> CLabel -> SDoc -pprDebugCLabel _ lbl +pprDebugCLabel :: CLabel -> SDoc +pprDebugCLabel lbl = case lbl of IdLabel{} -> ppr lbl <> (parens $ text "IdLabel") CmmLabel pkg _name _info @@ -533,38 +533,38 @@ mkPlainModuleInitLabel mod = PlainModuleInitLabel mod -- ----------------------------------------------------------------------------- -- Convert between different kinds of label -toClosureLbl :: Platform -> CLabel -> CLabel -toClosureLbl _ (IdLabel n c _) = IdLabel n c Closure -toClosureLbl platform l = pprPanic "toClosureLbl" (pprCLabel platform l) - -toSlowEntryLbl :: Platform -> CLabel -> CLabel -toSlowEntryLbl _ (IdLabel n c _) = IdLabel n c Slow -toSlowEntryLbl platform l = pprPanic "toSlowEntryLbl" (pprCLabel platform l) - -toRednCountsLbl :: Platform -> CLabel -> CLabel -toRednCountsLbl _ (IdLabel n c _) = IdLabel n c RednCounts -toRednCountsLbl platform l = pprPanic "toRednCountsLbl" (pprCLabel platform l) - -toEntryLbl :: Platform -> CLabel -> CLabel -toEntryLbl _ (IdLabel n c LocalInfoTable) = IdLabel n c LocalEntry -toEntryLbl _ (IdLabel n c ConInfoTable) = IdLabel n c ConEntry -toEntryLbl _ (IdLabel n c StaticInfoTable) = IdLabel n c StaticConEntry -toEntryLbl _ (IdLabel n c _) = IdLabel n c Entry -toEntryLbl _ (CaseLabel n CaseReturnInfo) = CaseLabel n CaseReturnPt -toEntryLbl _ (CmmLabel m str CmmInfo) = CmmLabel m str CmmEntry -toEntryLbl _ (CmmLabel m str CmmRetInfo) = CmmLabel m str CmmRet -toEntryLbl platform l = pprPanic "toEntryLbl" (pprCLabel platform l) - -toInfoLbl :: Platform -> CLabel -> CLabel -toInfoLbl _ (IdLabel n c Entry) = IdLabel n c InfoTable -toInfoLbl _ (IdLabel n c LocalEntry) = IdLabel n c LocalInfoTable -toInfoLbl _ (IdLabel n c ConEntry) = IdLabel n c ConInfoTable -toInfoLbl _ (IdLabel n c StaticConEntry) = IdLabel n c StaticInfoTable -toInfoLbl _ (IdLabel n c _) = IdLabel n c InfoTable -toInfoLbl _ (CaseLabel n CaseReturnPt) = CaseLabel n CaseReturnInfo -toInfoLbl _ (CmmLabel m str CmmEntry) = CmmLabel m str CmmInfo -toInfoLbl _ (CmmLabel m str CmmRet) = CmmLabel m str CmmRetInfo -toInfoLbl platform l = pprPanic "CLabel.toInfoLbl" (pprCLabel platform l) +toClosureLbl :: CLabel -> CLabel +toClosureLbl (IdLabel n c _) = IdLabel n c Closure +toClosureLbl l = pprPanic "toClosureLbl" (ppr l) + +toSlowEntryLbl :: CLabel -> CLabel +toSlowEntryLbl (IdLabel n c _) = IdLabel n c Slow +toSlowEntryLbl l = pprPanic "toSlowEntryLbl" (ppr l) + +toRednCountsLbl :: CLabel -> CLabel +toRednCountsLbl (IdLabel n c _) = IdLabel n c RednCounts +toRednCountsLbl l = pprPanic "toRednCountsLbl" (ppr l) + +toEntryLbl :: CLabel -> CLabel +toEntryLbl (IdLabel n c LocalInfoTable) = IdLabel n c LocalEntry +toEntryLbl (IdLabel n c ConInfoTable) = IdLabel n c ConEntry +toEntryLbl (IdLabel n c StaticInfoTable) = IdLabel n c StaticConEntry +toEntryLbl (IdLabel n c _) = IdLabel n c Entry +toEntryLbl (CaseLabel n CaseReturnInfo) = CaseLabel n CaseReturnPt +toEntryLbl (CmmLabel m str CmmInfo) = CmmLabel m str CmmEntry +toEntryLbl (CmmLabel m str CmmRetInfo) = CmmLabel m str CmmRet +toEntryLbl l = pprPanic "toEntryLbl" (ppr l) + +toInfoLbl :: CLabel -> CLabel +toInfoLbl (IdLabel n c Entry) = IdLabel n c InfoTable +toInfoLbl (IdLabel n c LocalEntry) = IdLabel n c LocalInfoTable +toInfoLbl (IdLabel n c ConEntry) = IdLabel n c ConInfoTable +toInfoLbl (IdLabel n c StaticConEntry) = IdLabel n c StaticInfoTable +toInfoLbl (IdLabel n c _) = IdLabel n c InfoTable +toInfoLbl (CaseLabel n CaseReturnPt) = CaseLabel n CaseReturnInfo +toInfoLbl (CmmLabel m str CmmEntry) = CmmLabel m str CmmInfo +toInfoLbl (CmmLabel m str CmmRet) = CmmLabel m str CmmRetInfo +toInfoLbl l = pprPanic "CLabel.toInfoLbl" (ppr l) -- ----------------------------------------------------------------------------- -- Does a CLabel refer to a CAF? @@ -1105,35 +1105,35 @@ pprDynamicLinkerAsmLabel platform dllInfo lbl = if platformOS platform == OSDarwin then if platformArch platform == ArchX86_64 then case dllInfo of - CodeStub -> char 'L' <> pprCLabel platform lbl <> text "$stub" - SymbolPtr -> char 'L' <> pprCLabel platform lbl <> text "$non_lazy_ptr" - GotSymbolPtr -> pprCLabel platform lbl <> text "@GOTPCREL" - GotSymbolOffset -> pprCLabel platform lbl + CodeStub -> char 'L' <> ppr lbl <> text "$stub" + SymbolPtr -> char 'L' <> ppr lbl <> text "$non_lazy_ptr" + GotSymbolPtr -> ppr lbl <> text "@GOTPCREL" + GotSymbolOffset -> ppr lbl else case dllInfo of - CodeStub -> char 'L' <> pprCLabel platform lbl <> text "$stub" - SymbolPtr -> char 'L' <> pprCLabel platform lbl <> text "$non_lazy_ptr" + CodeStub -> char 'L' <> ppr lbl <> text "$stub" + SymbolPtr -> char 'L' <> ppr lbl <> text "$non_lazy_ptr" _ -> panic "pprDynamicLinkerAsmLabel" else if osElfTarget (platformOS platform) then if platformArch platform == ArchPPC then case dllInfo of - CodeStub -> pprCLabel platform lbl <> text "@plt" - SymbolPtr -> text ".LC_" <> pprCLabel platform lbl + CodeStub -> ppr lbl <> text "@plt" + SymbolPtr -> text ".LC_" <> ppr lbl _ -> panic "pprDynamicLinkerAsmLabel" else if platformArch platform == ArchX86_64 then case dllInfo of - CodeStub -> pprCLabel platform lbl <> text "@plt" - GotSymbolPtr -> pprCLabel platform lbl <> text "@gotpcrel" - GotSymbolOffset -> pprCLabel platform lbl - SymbolPtr -> text ".LC_" <> pprCLabel platform lbl + CodeStub -> ppr lbl <> text "@plt" + GotSymbolPtr -> ppr lbl <> text "@gotpcrel" + GotSymbolOffset -> ppr lbl + SymbolPtr -> text ".LC_" <> ppr lbl else case dllInfo of - CodeStub -> pprCLabel platform lbl <> text "@plt" - SymbolPtr -> text ".LC_" <> pprCLabel platform lbl - GotSymbolPtr -> pprCLabel platform lbl <> text "@got" - GotSymbolOffset -> pprCLabel platform lbl <> text "@gotoff" + CodeStub -> ppr lbl <> text "@plt" + SymbolPtr -> text ".LC_" <> ppr lbl + GotSymbolPtr -> ppr lbl <> text "@got" + GotSymbolOffset -> ppr lbl <> text "@gotoff" else if platformOS platform == OSMinGW32 then case dllInfo of - SymbolPtr -> text "__imp_" <> pprCLabel platform lbl + SymbolPtr -> text "__imp_" <> ppr lbl _ -> panic "pprDynamicLinkerAsmLabel" else panic "pprDynamicLinkerAsmLabel" diff --git a/compiler/cmm/CmmBuildInfoTables.hs b/compiler/cmm/CmmBuildInfoTables.hs index 81d82d0b8a..ab829de499 100644 --- a/compiler/cmm/CmmBuildInfoTables.hs +++ b/compiler/cmm/CmmBuildInfoTables.hs @@ -51,7 +51,6 @@ import Control.Monad import Name import OptimizationFuel import Outputable -import Platform import SMRep import UniqSupply @@ -201,8 +200,8 @@ cafLattice = DataflowLattice "live cafs" Map.empty add where add _ (OldFact old) (NewFact new) = case old `Map.union` new of new' -> (changeIf $ Map.size new' > Map.size old, new') -cafTransfers :: Platform -> BwdTransfer CmmNode CAFSet -cafTransfers platform = mkBTransfer3 first middle last +cafTransfers :: BwdTransfer CmmNode CAFSet +cafTransfers = mkBTransfer3 first middle last where first _ live = live middle m live = foldExpDeep addCaf m live last l live = foldExpDeep addCaf l (joinOutFacts cafLattice l live) @@ -211,12 +210,11 @@ cafTransfers platform = mkBTransfer3 first middle last CmmLit (CmmLabelOff c _) -> add c set CmmLit (CmmLabelDiffOff c1 c2 _) -> add c1 $ add c2 set _ -> set - add l s = if hasCAF l then Map.insert (toClosureLbl platform l) () s + add l s = if hasCAF l then Map.insert (toClosureLbl l) () s else s -cafAnal :: Platform -> CmmGraph -> FuelUniqSM CAFEnv -cafAnal platform g - = liftM snd $ dataflowPassBwd g [] $ analBwd cafLattice (cafTransfers platform) +cafAnal :: CmmGraph -> FuelUniqSM CAFEnv +cafAnal g = liftM snd $ dataflowPassBwd g [] $ analBwd cafLattice cafTransfers ----------------------------------------------------------------------- -- Building the SRTs @@ -348,13 +346,13 @@ to_SRT top_srt off len bmp -- keep its CAFs live.) -- Any procedure referring to a non-static CAF c must keep live -- any CAF that is reachable from c. -localCAFInfo :: Platform -> CAFEnv -> CmmDecl -> Maybe (CLabel, CAFSet) -localCAFInfo _ _ (CmmData _ _) = Nothing -localCAFInfo platform cafEnv (CmmProc top_info top_l (CmmGraph {g_entry=entry})) = +localCAFInfo :: CAFEnv -> CmmDecl -> Maybe (CLabel, CAFSet) +localCAFInfo _ (CmmData _ _) = Nothing +localCAFInfo cafEnv (CmmProc top_info top_l (CmmGraph {g_entry=entry})) = case info_tbl top_info of CmmInfoTable { cit_rep = rep } | not (isStaticRep rep) - -> Just (toClosureLbl platform top_l, + -> Just (toClosureLbl top_l, expectJust "maybeBindCAFs" $ mapLookup entry cafEnv) _ -> Nothing diff --git a/compiler/cmm/CmmInfo.hs b/compiler/cmm/CmmInfo.hs index e4370696e1..fe0c104d1c 100644 --- a/compiler/cmm/CmmInfo.hs +++ b/compiler/cmm/CmmInfo.hs @@ -168,7 +168,7 @@ mkInfoTableContents platform , srt_lit, liveness_lit, slow_entry ] ; return (Nothing, Nothing, extra_bits, liveness_data) } where - slow_entry = CmmLabel (toSlowEntryLbl platform info_lbl) + slow_entry = CmmLabel (toSlowEntryLbl info_lbl) srt_lit = case srt_label of [] -> mkIntCLit 0 (lit:_rest) -> ASSERT( null _rest ) lit diff --git a/compiler/cmm/CmmPipeline.hs b/compiler/cmm/CmmPipeline.hs index 409623d58f..7361bbf385 100644 --- a/compiler/cmm/CmmPipeline.hs +++ b/compiler/cmm/CmmPipeline.hs @@ -149,8 +149,8 @@ cpsTop hsc_env (CmmProc h@(TopInfo {stack_info=StackInfo {arg_space=entry_off}}) mapM_ (dump Opt_D_dump_cmmz_split "Post splitting") gs ------------- More CAFs and foreign calls ------------ - cafEnv <- run $ cafAnal platform g - let localCAFs = catMaybes $ map (localCAFInfo platform cafEnv) gs + cafEnv <- run $ cafAnal g + let localCAFs = catMaybes $ map (localCAFInfo cafEnv) gs mbpprTrace "localCAFs" (ppr localCAFs) $ return () gs <- run $ mapM (lowerSafeForeignCalls areaMap) gs diff --git a/compiler/codeGen/StgCmmBind.hs b/compiler/codeGen/StgCmmBind.hs index 4f9d1b507c..3b166e3b6a 100644 --- a/compiler/codeGen/StgCmmBind.hs +++ b/compiler/codeGen/StgCmmBind.hs @@ -411,9 +411,7 @@ closureCodeBody top_lvl bndr cl_info _cc args arity body fv_details do { -- Allocate the global ticky counter, -- and establish the ticky-counter -- label for this block - ; dflags <- getDynFlags - ; let platform = targetPlatform dflags - ticky_ctr_lbl = closureRednCountsLabel platform cl_info + let ticky_ctr_lbl = closureRednCountsLabel cl_info ; emitTickyCounter cl_info (map stripNV args) ; setTickyCtrLabel ticky_ctr_lbl $ do @@ -470,10 +468,8 @@ mkSlowEntryCode :: ClosureInfo -> [LocalReg] -> FCode () mkSlowEntryCode _ [] = panic "entering a closure with no arguments?" mkSlowEntryCode cl_info arg_regs -- function closure is already in `Node' | Just (_, ArgGen _) <- closureFunInfo cl_info - = do dflags <- getDynFlags - let platform = targetPlatform dflags - slow_lbl = closureSlowEntryLabel platform cl_info - fast_lbl = closureLocalEntryLabel platform cl_info + = do let slow_lbl = closureSlowEntryLabel cl_info + fast_lbl = closureLocalEntryLabel cl_info -- mkDirectJump does not clobber `Node' containing function closure jump = mkDirectJump (mkLblExpr fast_lbl) (map (CmmReg . CmmLocal) arg_regs) diff --git a/compiler/codeGen/StgCmmClosure.hs b/compiler/codeGen/StgCmmClosure.hs index de7ab3d11a..aaecdd3e4b 100644 --- a/compiler/codeGen/StgCmmClosure.hs +++ b/compiler/codeGen/StgCmmClosure.hs @@ -87,7 +87,6 @@ import TcType import TyCon import BasicTypes import Outputable -import Platform import Constants import DynFlags import Util @@ -773,19 +772,19 @@ isToplevClosure (ClosureInfo { closureLFInfo = lf_info }) -- Label generation -------------------------------------- -staticClosureLabel :: Platform -> ClosureInfo -> CLabel -staticClosureLabel platform = toClosureLbl platform . closureInfoLabel +staticClosureLabel :: ClosureInfo -> CLabel +staticClosureLabel = toClosureLbl . closureInfoLabel -closureRednCountsLabel :: Platform -> ClosureInfo -> CLabel -closureRednCountsLabel platform = toRednCountsLbl platform . closureInfoLabel +closureRednCountsLabel :: ClosureInfo -> CLabel +closureRednCountsLabel = toRednCountsLbl . closureInfoLabel -closureSlowEntryLabel :: Platform -> ClosureInfo -> CLabel -closureSlowEntryLabel platform = toSlowEntryLbl platform . closureInfoLabel +closureSlowEntryLabel :: ClosureInfo -> CLabel +closureSlowEntryLabel = toSlowEntryLbl . closureInfoLabel -closureLocalEntryLabel :: Platform -> ClosureInfo -> CLabel -closureLocalEntryLabel platform - | tablesNextToCode = toInfoLbl platform . closureInfoLabel - | otherwise = toEntryLbl platform . closureInfoLabel +closureLocalEntryLabel :: ClosureInfo -> CLabel +closureLocalEntryLabel + | tablesNextToCode = toInfoLbl . closureInfoLabel + | otherwise = toEntryLbl . closureInfoLabel mkClosureInfoTableLabel :: Id -> LambdaFormInfo -> CLabel mkClosureInfoTableLabel id lf_info diff --git a/compiler/codeGen/StgCmmHeap.hs b/compiler/codeGen/StgCmmHeap.hs index 7b22c5726a..25161722f7 100644 --- a/compiler/codeGen/StgCmmHeap.hs +++ b/compiler/codeGen/StgCmmHeap.hs @@ -43,7 +43,6 @@ import IdInfo( CafInfo(..), mayHaveCafRefs ) import Module import FastString( mkFastString, fsLit ) import Constants -import DynFlags import Util ----------------------------------------------------------- @@ -329,11 +328,7 @@ entryHeapCheck :: ClosureInfo -> FCode () entryHeapCheck cl_info offset nodeSet arity args code - = do dflags <- getDynFlags - - let platform = targetPlatform dflags - - is_thunk = arity == 0 + = do let is_thunk = arity == 0 is_fastf = case closureFunInfo cl_info of Just (_, ArgGen _) -> False _otherwise -> True @@ -342,7 +337,7 @@ entryHeapCheck cl_info offset nodeSet arity args code setN = case nodeSet of Just n -> mkAssign nodeReg (CmmReg $ CmmLocal n) Nothing -> mkAssign nodeReg $ - CmmLit (CmmLabel $ staticClosureLabel platform cl_info) + CmmLit (CmmLabel $ staticClosureLabel cl_info) {- Thunks: Set R1 = node, jump GCEnter1 Function (fast): Set R1 = node, jump GCFun diff --git a/compiler/codeGen/StgCmmLayout.hs b/compiler/codeGen/StgCmmLayout.hs index 87e6d9f9dd..86986efdfa 100644 --- a/compiler/codeGen/StgCmmLayout.hs +++ b/compiler/codeGen/StgCmmLayout.hs @@ -51,7 +51,6 @@ import Id import Name import TyCon ( PrimRep(..) ) import BasicTypes ( RepArity ) -import DynFlags import StaticFlags import Constants @@ -405,9 +404,8 @@ emitClosureProcAndInfoTable top_lvl bndr lf_info info_tbl args body emitClosureAndInfoTable :: CmmInfoTable -> Convention -> [LocalReg] -> FCode () -> FCode () emitClosureAndInfoTable info_tbl conv args body - = do { dflags <- getDynFlags - ; blks <- getCode body - ; let entry_lbl = toEntryLbl (targetPlatform dflags) (cit_lbl info_tbl) + = do { blks <- getCode body + ; let entry_lbl = toEntryLbl (cit_lbl info_tbl) ; emitProcWithConvention conv info_tbl entry_lbl args blks } diff --git a/compiler/codeGen/StgCmmTicky.hs b/compiler/codeGen/StgCmmTicky.hs index 66dde86226..d0432315ab 100644 --- a/compiler/codeGen/StgCmmTicky.hs +++ b/compiler/codeGen/StgCmmTicky.hs @@ -97,8 +97,7 @@ emitTickyCounter cl_info args = ifTicky $ do { dflags <- getDynFlags ; mod_name <- getModuleName - ; let platform = targetPlatform dflags - ticky_ctr_label = closureRednCountsLabel platform cl_info + ; let ticky_ctr_label = closureRednCountsLabel cl_info arg_descr = map (showTypeCategory . idType) args fun_descr mod_name = ppr_for_ticky_name dflags mod_name (closureName cl_info) ; fun_descr_lit <- newStringCLit (fun_descr mod_name) diff --git a/compiler/nativeGen/AsmCodeGen.lhs b/compiler/nativeGen/AsmCodeGen.lhs index 0574e9246c..15dd2dc90a 100644 --- a/compiler/nativeGen/AsmCodeGen.lhs +++ b/compiler/nativeGen/AsmCodeGen.lhs @@ -375,7 +375,7 @@ cmmNativeGen dflags ncgImpl us cmm count let (withLiveness, usLive) = {-# SCC "regLiveness" #-} initUs usGen - $ mapUs (regLiveness platform) + $ mapUs regLiveness $ map natCmmTopToLive native dumpIfSet_dyn dflags diff --git a/compiler/nativeGen/RegAlloc/Graph/Main.hs b/compiler/nativeGen/RegAlloc/Graph/Main.hs index 4e359a1c79..bae3de8f16 100644 --- a/compiler/nativeGen/RegAlloc/Graph/Main.hs +++ b/compiler/nativeGen/RegAlloc/Graph/Main.hs @@ -120,7 +120,7 @@ regAlloc_spin dflags spinCount triv regsFree slotsFree debug_codeGraphs code -- build a map of the cost of spilling each instruction -- this will only actually be computed if we have to spill something. let spillCosts = foldl' plusSpillCostInfo zeroSpillCostInfo - $ map (slurpSpillCostInfo platform) code + $ map slurpSpillCostInfo code -- the function to choose regs to leave uncolored let spill = chooseSpill spillCosts @@ -220,7 +220,7 @@ regAlloc_spin dflags spinCount triv regsFree slotsFree debug_codeGraphs code -- NOTE: we have to reverse the SCCs here to get them back into the reverse-dependency -- order required by computeLiveness. If they're not in the correct order -- that function will panic. - code_relive <- mapM (regLiveness platform . reverseBlocksInTops) code_spilled + code_relive <- mapM (regLiveness . reverseBlocksInTops) code_spilled -- record what happened in this stage for debugging let stat = diff --git a/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs b/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs index c7b41de912..44e1ed7e0f 100644 --- a/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs +++ b/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs @@ -36,7 +36,6 @@ import UniqFM import UniqSet import Digraph (flattenSCCs) import Outputable -import Platform import State import Data.List (nub, minimumBy) @@ -71,11 +70,10 @@ plusSpillCostRecord (r1, a1, b1, c1) (r2, a2, b2, c2) -- and the number of instructions it was live on entry to (lifetime) -- slurpSpillCostInfo :: (Outputable instr, Instruction instr) - => Platform - -> LiveCmmDecl statics instr + => LiveCmmDecl statics instr -> SpillCostInfo -slurpSpillCostInfo _ cmm +slurpSpillCostInfo cmm = execState (countCmm cmm) zeroSpillCostInfo where countCmm CmmData{} = return () diff --git a/compiler/nativeGen/RegAlloc/Liveness.hs b/compiler/nativeGen/RegAlloc/Liveness.hs index 5ff89e811f..88023ec47f 100644 --- a/compiler/nativeGen/RegAlloc/Liveness.hs +++ b/compiler/nativeGen/RegAlloc/Liveness.hs @@ -663,20 +663,19 @@ sccBlocks blocks = stronglyConnCompFromEdgedVertices graph -- regLiveness :: (Outputable instr, Instruction instr) - => Platform - -> LiveCmmDecl statics instr + => LiveCmmDecl statics instr -> UniqSM (LiveCmmDecl statics instr) -regLiveness _ (CmmData i d) +regLiveness (CmmData i d) = returnUs $ CmmData i d -regLiveness _ (CmmProc info lbl []) +regLiveness (CmmProc info lbl []) | LiveInfo static mFirst _ _ <- info = returnUs $ CmmProc (LiveInfo static mFirst (Just mapEmpty) Map.empty) lbl [] -regLiveness _ (CmmProc info lbl sccs) +regLiveness (CmmProc info lbl sccs) | LiveInfo static mFirst _ liveSlotsOnEntry <- info = let (ann_sccs, block_live) = computeLiveness sccs |