diff options
Diffstat (limited to 'ghc/compiler/codeGen')
-rw-r--r-- | ghc/compiler/codeGen/CgBindery.lhs | 10 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgCase.lhs | 2 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgClosure.lhs | 2 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgCon.lhs | 4 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgExpr.lhs | 2 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgHeapery.lhs | 2 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgLetNoEscape.lhs | 2 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgProf.hs | 4 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgStackery.lhs | 2 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgTailCall.lhs | 2 | ||||
-rw-r--r-- | ghc/compiler/codeGen/ClosureInfo.lhs | 4 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CodeGen.lhs | 2 |
12 files changed, 19 insertions, 19 deletions
diff --git a/ghc/compiler/codeGen/CgBindery.lhs b/ghc/compiler/codeGen/CgBindery.lhs index 0f858777c2..5a953500a0 100644 --- a/ghc/compiler/codeGen/CgBindery.lhs +++ b/ghc/compiler/codeGen/CgBindery.lhs @@ -258,9 +258,9 @@ cgLookupPanic id pprPanic "cgPanic" (vcat [ppr id, ptext SLIT("static binds for:"), - vcat [ ppr (cg_id info) | info <- rngVarEnv static_binds ], + vcat [ ppr (cg_id info) | info <- varEnvElts static_binds ], ptext SLIT("local binds for:"), - vcat [ ppr (cg_id info) | info <- rngVarEnv local_binds ], + vcat [ ppr (cg_id info) | info <- varEnvElts local_binds ], ptext SLIT("SRT label") <+> pprCLabel srt ]) \end{code} @@ -277,7 +277,7 @@ we don't leave any (NoVolatile, NoStable) binds around... \begin{code} nukeVolatileBinds :: CgBindings -> CgBindings nukeVolatileBinds binds - = mkVarEnv (foldr keep_if_stable [] (rngVarEnv binds)) + = mkVarEnv (foldr keep_if_stable [] (varEnvElts binds)) where keep_if_stable (CgIdInfo { cg_stb = NoStableLoc }) acc = acc keep_if_stable info acc @@ -443,7 +443,7 @@ nukeDeadBindings live_vars = do let (dead_stk_slots, bs') = dead_slots live_vars [] [] - [ (cg_id b, b) | b <- rngVarEnv binds ] + [ (cg_id b, b) | b <- varEnvElts binds ] setBinds $ mkVarEnv bs' freeStackSlots dead_stk_slots \end{code} @@ -486,6 +486,6 @@ getLiveStackSlots :: FCode [VirtualSpOffset] getLiveStackSlots = do { binds <- getBinds ; return [off | CgIdInfo { cg_stb = VirStkLoc off, - cg_rep = rep } <- rngVarEnv binds, + cg_rep = rep } <- varEnvElts binds, isFollowableArg rep] } \end{code} diff --git a/ghc/compiler/codeGen/CgCase.lhs b/ghc/compiler/codeGen/CgCase.lhs index bdcc5ff17c..bdacd27ebd 100644 --- a/ghc/compiler/codeGen/CgCase.lhs +++ b/ghc/compiler/codeGen/CgCase.lhs @@ -1,7 +1,7 @@ % % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % -% $Id: CgCase.lhs,v 1.70 2004/08/13 13:25:45 simonmar Exp $ +% $Id: CgCase.lhs,v 1.71 2004/09/30 10:35:36 simonpj Exp $ % %******************************************************** %* * diff --git a/ghc/compiler/codeGen/CgClosure.lhs b/ghc/compiler/codeGen/CgClosure.lhs index dc5e9eae35..0c6ca4b76f 100644 --- a/ghc/compiler/codeGen/CgClosure.lhs +++ b/ghc/compiler/codeGen/CgClosure.lhs @@ -1,7 +1,7 @@ % % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % -% $Id: CgClosure.lhs,v 1.63 2004/08/13 13:05:54 simonmar Exp $ +% $Id: CgClosure.lhs,v 1.64 2004/09/30 10:35:39 simonpj Exp $ % \section[CgClosure]{Code generation for closures} diff --git a/ghc/compiler/codeGen/CgCon.lhs b/ghc/compiler/codeGen/CgCon.lhs index 6b3b36abaa..7dc5d75b41 100644 --- a/ghc/compiler/codeGen/CgCon.lhs +++ b/ghc/compiler/codeGen/CgCon.lhs @@ -45,7 +45,7 @@ import CostCentre ( currentOrSubsumedCCS, dontCareCCS, CostCentreStack, currentCCS ) import Constants ( mIN_INTLIKE, mAX_INTLIKE, mIN_CHARLIKE, mAX_CHARLIKE ) import TyCon ( TyCon, tyConDataCons, isEnumerationTyCon, tyConName ) -import DataCon ( DataCon, dataConRepArgTys, isNullaryDataCon, +import DataCon ( DataCon, dataConRepArgTys, isNullaryRepDataCon, isUnboxedTupleCon, dataConWorkId, dataConName, dataConRepArity ) @@ -404,7 +404,7 @@ static closure, for a constructor. cgDataCon :: DataCon -> Code cgDataCon data_con = do { -- Don't need any dynamic closure code for zero-arity constructors - whenC (not (isNullaryDataCon data_con)) + whenC (not (isNullaryRepDataCon data_con)) (emit_info dyn_cl_info tickyEnterDynCon) -- Dynamic-Closure first, to reduce forward references diff --git a/ghc/compiler/codeGen/CgExpr.lhs b/ghc/compiler/codeGen/CgExpr.lhs index d72c7c5a4c..ff405319c4 100644 --- a/ghc/compiler/codeGen/CgExpr.lhs +++ b/ghc/compiler/codeGen/CgExpr.lhs @@ -1,7 +1,7 @@ % % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % -% $Id: CgExpr.lhs,v 1.59 2004/08/13 13:05:58 simonmar Exp $ +% $Id: CgExpr.lhs,v 1.60 2004/09/30 10:35:43 simonpj Exp $ % %******************************************************** %* * diff --git a/ghc/compiler/codeGen/CgHeapery.lhs b/ghc/compiler/codeGen/CgHeapery.lhs index 6abffe72dc..5e6c122f7c 100644 --- a/ghc/compiler/codeGen/CgHeapery.lhs +++ b/ghc/compiler/codeGen/CgHeapery.lhs @@ -1,7 +1,7 @@ % % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % -% $Id: CgHeapery.lhs,v 1.40 2004/08/13 13:06:00 simonmar Exp $ +% $Id: CgHeapery.lhs,v 1.41 2004/09/30 10:35:45 simonpj Exp $ % \section[CgHeapery]{Heap management functions} diff --git a/ghc/compiler/codeGen/CgLetNoEscape.lhs b/ghc/compiler/codeGen/CgLetNoEscape.lhs index 3ea05974f6..39860f4ee0 100644 --- a/ghc/compiler/codeGen/CgLetNoEscape.lhs +++ b/ghc/compiler/codeGen/CgLetNoEscape.lhs @@ -1,7 +1,7 @@ % % (c) The GRASP/AQUA Project, Glasgow University, 1993-1998 % -% $Id: CgLetNoEscape.lhs,v 1.25 2004/08/13 13:06:03 simonmar Exp $ +% $Id: CgLetNoEscape.lhs,v 1.26 2004/09/30 10:35:47 simonpj Exp $ % %******************************************************** %* * diff --git a/ghc/compiler/codeGen/CgProf.hs b/ghc/compiler/codeGen/CgProf.hs index 30f801dba3..0c2381b14a 100644 --- a/ghc/compiler/codeGen/CgProf.hs +++ b/ghc/compiler/codeGen/CgProf.hs @@ -389,9 +389,9 @@ emitSetCCC :: CostCentre -> Code emitSetCCC cc | not opt_SccProfilingOn = nopC | otherwise = do - ASSERTM(sccAbleCostCentre cc) tmp <- newTemp wordRep - pushCostCentre tmp curCCS cc + ASSERT( sccAbleCostCentre cc ) + pushCostCentre tmp curCCS cc stmtC (CmmStore curCCSAddr (CmmReg tmp)) when (isSccCountCostCentre cc) $ stmtC (bumpSccCount curCCS) diff --git a/ghc/compiler/codeGen/CgStackery.lhs b/ghc/compiler/codeGen/CgStackery.lhs index 2dddb3d34f..7cb310d521 100644 --- a/ghc/compiler/codeGen/CgStackery.lhs +++ b/ghc/compiler/codeGen/CgStackery.lhs @@ -1,7 +1,7 @@ % % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % -% $Id: CgStackery.lhs,v 1.26 2004/08/17 15:23:48 simonpj Exp $ +% $Id: CgStackery.lhs,v 1.27 2004/09/30 10:35:49 simonpj Exp $ % \section[CgStackery]{Stack management functions} diff --git a/ghc/compiler/codeGen/CgTailCall.lhs b/ghc/compiler/codeGen/CgTailCall.lhs index 982891b2f7..98c075d31d 100644 --- a/ghc/compiler/codeGen/CgTailCall.lhs +++ b/ghc/compiler/codeGen/CgTailCall.lhs @@ -1,7 +1,7 @@ % % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % -% $Id: CgTailCall.lhs,v 1.39 2004/08/13 13:06:13 simonmar Exp $ +% $Id: CgTailCall.lhs,v 1.40 2004/09/30 10:35:50 simonpj Exp $ % %******************************************************** %* * diff --git a/ghc/compiler/codeGen/ClosureInfo.lhs b/ghc/compiler/codeGen/ClosureInfo.lhs index 0abf831c51..476aa2aa95 100644 --- a/ghc/compiler/codeGen/ClosureInfo.lhs +++ b/ghc/compiler/codeGen/ClosureInfo.lhs @@ -65,7 +65,7 @@ import CmdLineOpts ( opt_SccProfilingOn, opt_OmitBlackHoling, opt_Parallel, opt_DoTickyProfiling, opt_SMP ) import Id ( Id, idType, idArity, idName ) -import DataCon ( DataCon, dataConTyCon, isNullaryDataCon, dataConName ) +import DataCon ( DataCon, dataConTyCon, isNullaryRepDataCon, dataConName ) import Name ( Name, nameUnique, getOccName, getOccString ) import OccName ( occNameUserString ) import Type ( isUnLiftedType, Type, repType, splitTyConApp_maybe ) @@ -663,7 +663,7 @@ staticClosureNeedsLink :: ClosureInfo -> Bool staticClosureNeedsLink (ClosureInfo { closureSRT = srt }) = needsSRT srt staticClosureNeedsLink (ConInfo { closureSMRep = sm_rep, closureCon = con }) - = not (isNullaryDataCon con) && not_nocaf_constr + = not (isNullaryRepDataCon con) && not_nocaf_constr where not_nocaf_constr = case sm_rep of diff --git a/ghc/compiler/codeGen/CodeGen.lhs b/ghc/compiler/codeGen/CodeGen.lhs index d7f2f70c43..7ee581a45f 100644 --- a/ghc/compiler/codeGen/CodeGen.lhs +++ b/ghc/compiler/codeGen/CodeGen.lhs @@ -53,7 +53,7 @@ import OccName ( mkLocalOcc ) import TyCon ( isDataTyCon ) import Module ( Module, mkModuleName ) import ErrUtils ( dumpIfSet_dyn, showPass ) -import Panic ( assertPanic, trace ) +import Panic ( assertPanic ) import qualified Module ( moduleName ) #ifdef DEBUG |