diff options
Diffstat (limited to 'compiler')
-rw-r--r-- | compiler/cmm/CmmDecl.hs | 9 | ||||
-rw-r--r-- | compiler/cmm/CmmInfo.hs | 13 | ||||
-rw-r--r-- | compiler/cmm/CmmParse.y | 14 | ||||
-rw-r--r-- | compiler/cmm/CmmProcPoint.hs | 2 | ||||
-rw-r--r-- | compiler/codeGen/CgInfoTbls.hs | 13 | ||||
-rw-r--r-- | compiler/codeGen/ClosureInfo.lhs | 16 | ||||
-rw-r--r-- | compiler/codeGen/StgCmmClosure.hs | 16 | ||||
-rw-r--r-- | compiler/codeGen/StgCmmLayout.hs | 6 |
8 files changed, 40 insertions, 49 deletions
diff --git a/compiler/cmm/CmmDecl.hs b/compiler/cmm/CmmDecl.hs index 28279f2dca..552878e7bb 100644 --- a/compiler/cmm/CmmDecl.hs +++ b/compiler/cmm/CmmDecl.hs @@ -55,7 +55,7 @@ newtype GenCmm d h g = Cmm [GenCmmTop d h g] data GenCmmTop d h g = CmmProc -- A procedure h -- Extra header such as the info table - CLabel -- Used to generate both info & entry labels (though the info table label is in 'h' in RawCmmTop) + CLabel -- Entry label g -- Control-flow graph for the procedure's code | CmmData -- Static data @@ -70,18 +70,13 @@ data GenCmmTop d h g -- Info table as a haskell data type data CmmInfoTable = CmmInfoTable - LocalInfoTable + CLabel -- Info table label HasStaticClosure ProfilingInfo ClosureTypeTag -- Int ClosureTypeInfo | CmmNonInfoTable -- Procedure doesn't need an info table --- | If the table is local, we don't export its identifier even if the --- corresponding Id is exported. It's always safe to say 'False' --- here, but it might save symbols to say 'True' -type LocalInfoTable = Bool - type HasStaticClosure = Bool -- TODO: The GC target shouldn't really be part of CmmInfo diff --git a/compiler/cmm/CmmInfo.hs b/compiler/cmm/CmmInfo.hs index 47d0c8b004..e463b3619f 100644 --- a/compiler/cmm/CmmInfo.hs +++ b/compiler/cmm/CmmInfo.hs @@ -1,5 +1,5 @@ module CmmInfo ( - emptyContInfoTable, + mkEmptyContInfoTable, cmmToRawCmm, mkInfoTable, ) where @@ -27,9 +27,9 @@ import UniqSupply import Data.Bits -- When we split at proc points, we need an empty info table. -emptyContInfoTable :: CmmInfoTable -emptyContInfoTable = CmmInfoTable False False (ProfilingInfo zero zero) rET_SMALL - (ContInfo [] NoC_SRT) +mkEmptyContInfoTable :: CLabel -> CmmInfoTable +mkEmptyContInfoTable info_lbl = CmmInfoTable info_lbl False (ProfilingInfo zero zero) rET_SMALL + (ContInfo [] NoC_SRT) where zero = CmmInt 0 wordWidth cmmToRawCmm :: [Cmm] -> IO [RawCmm] @@ -80,9 +80,8 @@ mkInfoTable uniq (CmmProc (CmmInfo _ _ info) entry_label blocks) = -- Code without an info table. Easy. CmmNonInfoTable -> [CmmProc Nothing entry_label blocks] - CmmInfoTable is_local _ (ProfilingInfo ty_prof cl_prof) type_tag type_info -> - let info_label = (if is_local then localiseLabel else id) $ entryLblToInfoLbl entry_label - ty_prof' = makeRelativeRefTo info_label ty_prof + CmmInfoTable info_label _ (ProfilingInfo ty_prof cl_prof) type_tag type_info -> + let ty_prof' = makeRelativeRefTo info_label ty_prof cl_prof' = makeRelativeRefTo info_label cl_prof in case type_info of -- A function entry point. diff --git a/compiler/cmm/CmmParse.y b/compiler/cmm/CmmParse.y index 2d59fe751e..9d9136e18b 100644 --- a/compiler/cmm/CmmParse.y +++ b/compiler/cmm/CmmParse.y @@ -266,7 +266,7 @@ info :: { ExtFCode (CLabel, CmmInfoTable, [Maybe LocalReg]) } {% withThisPackage $ \pkg -> do prof <- profilingInfo $11 $13 return (mkCmmEntryLabel pkg $3, - CmmInfoTable False False prof (fromIntegral $9) + CmmInfoTable (mkCmmInfoLabel pkg $3) False prof (fromIntegral $9) (ThunkInfo (fromIntegral $5, fromIntegral $7) NoC_SRT), []) } @@ -275,7 +275,7 @@ info :: { ExtFCode (CLabel, CmmInfoTable, [Maybe LocalReg]) } {% withThisPackage $ \pkg -> do prof <- profilingInfo $11 $13 return (mkCmmEntryLabel pkg $3, - CmmInfoTable False False prof (fromIntegral $9) + CmmInfoTable (mkCmmInfoLabel pkg $3) False prof (fromIntegral $9) (FunInfo (fromIntegral $5, fromIntegral $7) NoC_SRT 0 -- Arity zero (ArgSpec (fromIntegral $15)) @@ -290,7 +290,7 @@ info :: { ExtFCode (CLabel, CmmInfoTable, [Maybe LocalReg]) } {% withThisPackage $ \pkg -> do prof <- profilingInfo $11 $13 return (mkCmmEntryLabel pkg $3, - CmmInfoTable False False prof (fromIntegral $9) + CmmInfoTable (mkCmmInfoLabel pkg $3) False prof (fromIntegral $9) (FunInfo (fromIntegral $5, fromIntegral $7) NoC_SRT (fromIntegral $17) (ArgSpec (fromIntegral $15)) zeroCLit), @@ -306,7 +306,7 @@ info :: { ExtFCode (CLabel, CmmInfoTable, [Maybe LocalReg]) } -- but that's the way the old code did it we can fix it some other time. desc_lit <- code $ mkStringCLit $13 return (mkCmmEntryLabel pkg $3, - CmmInfoTable False False prof (fromIntegral $11) + CmmInfoTable (mkCmmInfoLabel pkg $3) False prof (fromIntegral $11) (ConstrInfo (fromIntegral $5, fromIntegral $7) (fromIntegral $9) desc_lit), []) } @@ -315,7 +315,7 @@ info :: { ExtFCode (CLabel, CmmInfoTable, [Maybe LocalReg]) } {% withThisPackage $ \pkg -> do prof <- profilingInfo $9 $11 return (mkCmmEntryLabel pkg $3, - CmmInfoTable False False prof (fromIntegral $7) + CmmInfoTable (mkCmmInfoLabel pkg $3) False prof (fromIntegral $7) (ThunkSelectorInfo (fromIntegral $5) NoC_SRT), []) } @@ -324,7 +324,7 @@ info :: { ExtFCode (CLabel, CmmInfoTable, [Maybe LocalReg]) } {% withThisPackage $ \pkg -> do let infoLabel = mkCmmInfoLabel pkg $3 return (mkCmmRetLabel pkg $3, - CmmInfoTable False False (ProfilingInfo zeroCLit zeroCLit) (fromIntegral $5) + CmmInfoTable (mkCmmInfoLabel pkg $3) False (ProfilingInfo zeroCLit zeroCLit) (fromIntegral $5) (ContInfo [] NoC_SRT), []) } @@ -333,7 +333,7 @@ info :: { ExtFCode (CLabel, CmmInfoTable, [Maybe LocalReg]) } {% withThisPackage $ \pkg -> do live <- sequence (map (liftM Just) $7) return (mkCmmRetLabel pkg $3, - CmmInfoTable False False (ProfilingInfo zeroCLit zeroCLit) (fromIntegral $5) + CmmInfoTable (mkCmmInfoLabel pkg $3) False (ProfilingInfo zeroCLit zeroCLit) (fromIntegral $5) (ContInfo live NoC_SRT), live) } diff --git a/compiler/cmm/CmmProcPoint.hs b/compiler/cmm/CmmProcPoint.hs index b608b291d4..6af8a69e77 100644 --- a/compiler/cmm/CmmProcPoint.hs +++ b/compiler/cmm/CmmProcPoint.hs @@ -463,7 +463,7 @@ splitAtProcPoints entry_label callPPs procPoints procMap CmmProc (TopInfo {info_tbl=info_tbl, stack_info=stack_info}) top_l (replacePPIds g) else - CmmProc (TopInfo {info_tbl=emptyContInfoTable, stack_info=stack_info}) + CmmProc (TopInfo {info_tbl=mkEmptyContInfoTable (entryLblToInfoLbl lbl), stack_info=stack_info}) lbl (replacePPIds g) where lbl = expectJust "pp label" $ Map.lookup bid procLabels to_proc (bid, (stack_info, g)) = diff --git a/compiler/codeGen/CgInfoTbls.hs b/compiler/codeGen/CgInfoTbls.hs index 76a433b48e..dbd22f3906 100644 --- a/compiler/codeGen/CgInfoTbls.hs +++ b/compiler/codeGen/CgInfoTbls.hs @@ -57,9 +57,7 @@ emitClosureCodeAndInfoTable :: ClosureInfo -> [CmmFormal] -> CgStmts -> Code emitClosureCodeAndInfoTable cl_info args body = do { blks <- cgStmtsToBlocks body ; info <- mkCmmInfo cl_info - ; emitInfoTableAndCode (infoLblToEntryLbl info_lbl) info args blks } - where - info_lbl = infoTableLabelFromCI cl_info + ; emitInfoTableAndCode (entryLabelFromCI cl_info) info args blks } -- We keep the *zero-indexed* tag in the srt_len field of the info -- table of a data constructor. @@ -84,12 +82,12 @@ mkCmmInfo cl_info = do info = ConstrInfo (ptrs, nptrs) (fromIntegral (dataConTagZ con)) conName - return $ CmmInfo gc_target Nothing (CmmInfoTable False False prof cl_type info) + return $ CmmInfo gc_target Nothing (CmmInfoTable (infoTableLabelFromCI cl_info) False prof cl_type info) ClosureInfo { closureName = name, closureLFInfo = lf_info, closureSRT = srt } -> - return $ CmmInfo gc_target Nothing (CmmInfoTable (closureInfoLocal cl_info) False prof cl_type info) + return $ CmmInfo gc_target Nothing (CmmInfoTable (infoTableLabelFromCI cl_info) False prof cl_type info) where info = case lf_info of @@ -142,16 +140,17 @@ emitReturnTarget name stmts ; let info = CmmInfo gc_target Nothing - (CmmInfoTable False False + (CmmInfoTable info_lbl False (ProfilingInfo zeroCLit zeroCLit) rET_SMALL -- cmmToRawCmm may convert it to rET_BIG (ContInfo frame srt_info)) - ; emitInfoTableAndCode (infoLblToEntryLbl info_lbl) info args blks + ; emitInfoTableAndCode entry_lbl info args blks ; return info_lbl } where args = {- trace "emitReturnTarget: missing args" -} [] uniq = getUnique name info_lbl = mkReturnInfoLabel uniq + entry_lbl = mkReturnPtLabel uniq -- The gc_target is to inform the CPS pass when it inserts a stack check. -- Since that pass isn't used yet we'll punt for now. diff --git a/compiler/codeGen/ClosureInfo.lhs b/compiler/codeGen/ClosureInfo.lhs index ad2ea4fddd..6964de7273 100644 --- a/compiler/codeGen/ClosureInfo.lhs +++ b/compiler/codeGen/ClosureInfo.lhs @@ -29,7 +29,7 @@ module ClosureInfo ( closureGoodStuffSize, closurePtrsSize, slopSize, - infoTableLabelFromCI, + infoTableLabelFromCI, entryLabelFromCI, closureLabelFromCI, isLFThunk, closureUpdReqd, closureNeedsUpdSpace, closureIsThunk, @@ -50,7 +50,7 @@ module ClosureInfo ( isToplevClosure, closureValDescr, closureTypeDescr, -- profiling - closureInfoLocal, isStaticClosure, + isStaticClosure, cafBlackHoleClosureInfo, staticClosureNeedsLink, @@ -847,10 +847,6 @@ staticClosureRequired _ _ _ = True %************************************************************************ \begin{code} -closureInfoLocal :: ClosureInfo -> Bool -closureInfoLocal ClosureInfo{ closureInfLcl = lcl } = lcl -closureInfoLocal ConInfo{} = False - isStaticClosure :: ClosureInfo -> Bool isStaticClosure cl_info = isStaticRep (closureSMRep cl_info) @@ -931,8 +927,9 @@ Label generation. \begin{code} infoTableLabelFromCI :: ClosureInfo -> CLabel infoTableLabelFromCI cl@(ClosureInfo { closureName = name, - closureLFInfo = lf_info }) - = case lf_info of + closureLFInfo = lf_info, + closureInfLcl = is_lcl }) + = (if is_lcl then localiseLabel else id) $ case lf_info of LFBlackHole info -> info LFThunk _ _ upd_flag (SelectorThunk offset) _ -> @@ -954,6 +951,9 @@ infoTableLabelFromCI cl@(ConInfo { closureCon = con, where name = dataConName con +entryLabelFromCI :: ClosureInfo -> CLabel +entryLabelFromCI = infoLblToEntryLbl . infoTableLabelFromCI + -- ClosureInfo for a closure (as opposed to a constructor) is always local closureLabelFromCI :: ClosureInfo -> CLabel closureLabelFromCI cl@(ClosureInfo { closureName = nm }) = mkLocalClosureLabel nm $ clHasCafRefs cl diff --git a/compiler/codeGen/StgCmmClosure.hs b/compiler/codeGen/StgCmmClosure.hs index 7c4f8bc8b8..7a6f0bbc45 100644 --- a/compiler/codeGen/StgCmmClosure.hs +++ b/compiler/codeGen/StgCmmClosure.hs @@ -35,7 +35,7 @@ module StgCmmClosure ( closureGoodStuffSize, closurePtrsSize, slopSize, - closureName, infoTableLabelFromCI, + closureName, infoTableLabelFromCI, entryLabelFromCI, closureLabelFromCI, closureTypeInfo, closureLFInfo, isLFThunk,closureSMRep, closureUpdReqd, @@ -56,7 +56,7 @@ module StgCmmClosure ( isToplevClosure, closureValDescr, closureTypeDescr, -- profiling - closureInfoLocal, isStaticClosure, + isStaticClosure, cafBlackHoleClosureInfo, staticClosureNeedsLink, clHasCafRefs @@ -938,10 +938,6 @@ staticClosureNeedsLink (ConInfo { closureSMRep = sm_rep, closureCon = con }) GenericRep _ _ _ ConstrNoCaf -> False _other -> True -closureInfoLocal :: ClosureInfo -> Bool -closureInfoLocal ClosureInfo{ closureInfLcl = lcl } = lcl -closureInfoLocal ConInfo{} = False - isStaticClosure :: ClosureInfo -> Bool isStaticClosure cl_info = isStaticRep (closureSMRep cl_info) @@ -998,8 +994,9 @@ isToplevClosure _ = False infoTableLabelFromCI :: ClosureInfo -> CLabel infoTableLabelFromCI cl@(ClosureInfo { closureName = name, - closureLFInfo = lf_info }) - = case lf_info of + closureLFInfo = lf_info, + closureInfLcl = is_lcl }) + = (if is_lcl then localiseLabel else id) $ case lf_info of LFBlackHole info -> info LFThunk _ _ upd_flag (SelectorThunk offset) _ -> @@ -1020,6 +1017,9 @@ infoTableLabelFromCI cl@(ConInfo { closureCon = con, closureSMRep = rep }) where name = dataConName con +entryLabelFromCI :: ClosureInfo -> CLabel +entryLabelFromCI = infoLblToEntryLbl . infoTableLabelFromCI + -- ClosureInfo for a closure (as opposed to a constructor) is always local closureLabelFromCI :: ClosureInfo -> CLabel closureLabelFromCI cl@(ClosureInfo { closureName = nm }) = diff --git a/compiler/codeGen/StgCmmLayout.hs b/compiler/codeGen/StgCmmLayout.hs index 278c41aef2..63fc840845 100644 --- a/compiler/codeGen/StgCmmLayout.hs +++ b/compiler/codeGen/StgCmmLayout.hs @@ -481,10 +481,8 @@ emitClosureAndInfoTable :: emitClosureAndInfoTable cl_info conv args body = do { info <- mkCmmInfo cl_info ; blks <- getCode body - ; emitProcWithConvention conv info (infoLblToEntryLbl info_lbl) args blks + ; emitProcWithConvention conv info (entryLabelFromCI cl_info) args blks } - where - info_lbl = infoTableLabelFromCI cl_info -- Convert from 'ClosureInfo' to 'CmmInfoTable'. -- Not used for return points. (The 'smRepClosureTypeInt' call would panic.) @@ -496,7 +494,7 @@ mkCmmInfo cl_info ad_lit <- mkStringCLit (closureValDescr cl_info) return $ ProfilingInfo fd_lit ad_lit else return $ ProfilingInfo (mkIntCLit 0) (mkIntCLit 0) - ; return (CmmInfoTable (closureInfoLocal cl_info) (isStaticClosure cl_info) prof cl_type info) } + ; return (CmmInfoTable (infoTableLabelFromCI cl_info) (isStaticClosure cl_info) prof cl_type info) } where k_with_con_name con_info con info_lbl = do cstr <- mkByteStringCLit $ dataConIdentity con |