diff options
Diffstat (limited to 'ghc/compiler/codeGen')
-rw-r--r-- | ghc/compiler/codeGen/CgForeignCall.hs | 11 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgHeapery.lhs | 4 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgPrimOp.hs | 5 | ||||
-rw-r--r-- | ghc/compiler/codeGen/ClosureInfo.lhs | 39 | ||||
-rw-r--r-- | ghc/compiler/codeGen/SMRep.lhs | 5 |
5 files changed, 24 insertions, 40 deletions
diff --git a/ghc/compiler/codeGen/CgForeignCall.hs b/ghc/compiler/codeGen/CgForeignCall.hs index 155e30205c..e56189ae11 100644 --- a/ghc/compiler/codeGen/CgForeignCall.hs +++ b/ghc/compiler/codeGen/CgForeignCall.hs @@ -32,7 +32,7 @@ import MachOp import SMRep import ForeignCall import Constants -import StaticFlags ( opt_SccProfilingOn, opt_SMP ) +import StaticFlags ( opt_SccProfilingOn ) import Outputable import Monad ( when ) @@ -85,11 +85,10 @@ emitForeignCall results (CCall (CCallSpec target cconv safety)) args live ) stmtC (the_call vols) stmtC (CmmCall (CmmForeignCall resumeThread CCallConv) - (if opt_SMP then [(CmmGlobal BaseReg, PtrHint)] else []) - -- Assign the result to BaseReg: we might now have - -- a different Capability! Small optimisation: - -- only do this in SMP mode, where there are >1 - -- Capabilities. + [ (CmmGlobal BaseReg, PtrHint) ] + -- Assign the result to BaseReg: we + -- might now have a different + -- Capability! [ (CmmReg id, PtrHint) ] (Just vols) ) diff --git a/ghc/compiler/codeGen/CgHeapery.lhs b/ghc/compiler/codeGen/CgHeapery.lhs index 78a6f78053..184af904df 100644 --- a/ghc/compiler/codeGen/CgHeapery.lhs +++ b/ghc/compiler/codeGen/CgHeapery.lhs @@ -23,7 +23,6 @@ module CgHeapery ( #include "HsVersions.h" -import Constants ( mIN_UPD_SIZE ) import StgSyn ( AltType(..) ) import CLabel ( CLabel, mkRtsCodeLabel ) import CgUtils ( mkWordCLit, cmmRegOffW, cmmOffsetW, @@ -212,8 +211,7 @@ mkStaticClosureFields cl_info ccs caf_refs payload padding_wds | not is_caf = [] - | otherwise = replicate n (mkIntCLit 0) -- a bunch of 0s - where n = max 0 (mIN_UPD_SIZE - length payload) + | otherwise = ASSERT(null payload) [mkIntCLit 0] static_link_field | is_caf || staticClosureNeedsLink cl_info = [static_link_value] diff --git a/ghc/compiler/codeGen/CgPrimOp.hs b/ghc/compiler/codeGen/CgPrimOp.hs index 245a245cf4..7de4516af7 100644 --- a/ghc/compiler/codeGen/CgPrimOp.hs +++ b/ghc/compiler/codeGen/CgPrimOp.hs @@ -28,7 +28,7 @@ import SMRep import PrimOp ( PrimOp(..) ) import SMRep ( tablesNextToCode ) import Constants ( wORD_SIZE, wORD_SIZE_IN_BITS ) -import StaticFlags ( opt_Parallel, opt_SMP ) +import StaticFlags ( opt_Parallel ) import Outputable -- --------------------------------------------------------------------------- @@ -113,9 +113,6 @@ emitPrimOp [res_r,res_c] IntSubCOp [aa,bb] live emitPrimOp [res] ParOp [arg] live - | not (opt_Parallel || opt_SMP) - = stmtC (CmmAssign res (CmmLit (mkIntCLit 1))) - | otherwise = do -- for now, just implement this in a C function -- later, we might want to inline it. diff --git a/ghc/compiler/codeGen/ClosureInfo.lhs b/ghc/compiler/codeGen/ClosureInfo.lhs index a5362e60e0..84d9dd95ef 100644 --- a/ghc/compiler/codeGen/ClosureInfo.lhs +++ b/ghc/compiler/codeGen/ClosureInfo.lhs @@ -61,11 +61,10 @@ import SMRep -- all of it import CLabel -import Constants ( mIN_UPD_SIZE, mIN_SIZE_NonUpdHeapObject ) +import Constants ( mIN_PAYLOAD_SIZE ) import Packages ( isDllName, HomeModules ) import StaticFlags ( opt_SccProfilingOn, opt_OmitBlackHoling, - opt_Parallel, opt_DoTickyProfiling, - opt_SMP ) + opt_Parallel, opt_DoTickyProfiling ) import Id ( Id, idType, idArity, idName ) import DataCon ( DataCon, dataConTyCon, isNullaryRepDataCon, dataConName ) import Name ( Name, nameUnique, getOccName, getOccString ) @@ -387,16 +386,8 @@ Computing slop size. WARNING: this looks dodgy --- it has deep knowledge of what the storage manager does with the various representations... -Slop Requirements: - - - Updatable closures must be mIN_UPD_SIZE. - - - Heap-resident Closures must be mIN_SIZE_NonUpdHeapObject - (to make room for an StgEvacuated during GC). - -In SMP mode, we don't play the mIN_UPD_SIZE game. Instead, every -thunk gets an extra padding word in the header, which takes the -the updated value. +Slop Requirements: every thunk gets an extra padding word in the +header, which takes the the updated value. \begin{code} slopSize cl_info = computeSlopSize payload_size cl_info @@ -423,16 +414,14 @@ minPayloadSize smrep updatable BlackHoleRep -> min_upd_size GenericRep _ _ _ _ | updatable -> min_upd_size GenericRep True _ _ _ -> 0 -- static - GenericRep False _ _ _ -> mIN_SIZE_NonUpdHeapObject + GenericRep False _ _ _ -> mIN_PAYLOAD_SIZE -- ^^^^^___ dynamic where - min_upd_size - | opt_SMP = ASSERT(mIN_SIZE_NonUpdHeapObject <= - sIZEOF_StgSMPThunkHeader) - 0 -- check that we already have enough - -- room for mIN_SIZE_NonUpdHeapObject, - -- due to the extra header word in SMP - | otherwise = mIN_UPD_SIZE + min_upd_size = + ASSERT(mIN_PAYLOAD_SIZE <= sIZEOF_StgSMPThunkHeader) + 0 -- check that we already have enough + -- room for mIN_SIZE_NonUpdHeapObject, + -- due to the extra header word in SMP \end{code} %************************************************************************ @@ -600,9 +589,11 @@ getCallMethod hmods name (LFThunk _ _ updatable std_form_info is_fun) n_args -- is the fast-entry code] | updatable || opt_DoTickyProfiling -- to catch double entry - || opt_SMP -- Always enter via node on SMP, since the - -- thunk might have been blackholed in the - -- meantime. + {- OLD: || opt_SMP + I decided to remove this, because in SMP mode it doesn't matter + if we enter the same thunk multiple times, so the optimisation + of jumping directly to the entry code is still valid. --SDM + -} = ASSERT( n_args == 0 ) EnterIt | otherwise -- Jump direct to code for single-entry thunks diff --git a/ghc/compiler/codeGen/SMRep.lhs b/ghc/compiler/codeGen/SMRep.lhs index b0b1b140f7..c807703b13 100644 --- a/ghc/compiler/codeGen/SMRep.lhs +++ b/ghc/compiler/codeGen/SMRep.lhs @@ -43,7 +43,7 @@ import Type ( Type, typePrimRep, PrimRep(..) ) import TyCon ( TyCon, tyConPrimRep ) import MachOp-- ( MachRep(..), MachHint(..), wordRep ) import StaticFlags ( opt_SccProfilingOn, opt_GranMacros, - opt_Unregisterised, opt_SMP ) + opt_Unregisterised ) import Constants import Outputable @@ -289,8 +289,7 @@ arrPtrsHdrSize = fixedHdrSize*wORD_SIZE + sIZEOF_StgMutArrPtrs_NoHdr -- Thunks have an extra header word on SMP, so the update doesn't -- splat the payload. thunkHdrSize :: WordOff -thunkHdrSize | opt_SMP = fixedHdrSize + smp_hdr - | otherwise = fixedHdrSize +thunkHdrSize = fixedHdrSize + smp_hdr where smp_hdr = sIZEOF_StgSMPThunkHeader `quot` wORD_SIZE \end{code} |