diff options
author | Ian Lynagh <ian@well-typed.com> | 2012-10-16 15:28:26 +0100 |
---|---|---|
committer | Ian Lynagh <ian@well-typed.com> | 2012-10-16 16:08:38 +0100 |
commit | cd33eefd0467ae7ee4d22f16fcaaccfd33f18cb5 (patch) | |
tree | 30fb18578f1c5c81fef7ccc6ec5879a41fd4e5c0 /compiler/codeGen | |
parent | 6759e5a482d927870c90efe97b820d492785a6fd (diff) | |
download | haskell-cd33eefd0467ae7ee4d22f16fcaaccfd33f18cb5.tar.gz |
Some alpha renaming
Mostly d -> g (matching DynFlag -> GeneralFlag).
Also renamed if* to when*, matching the Haskell if/when names
Diffstat (limited to 'compiler/codeGen')
24 files changed, 53 insertions, 53 deletions
diff --git a/compiler/codeGen/CgCallConv.hs b/compiler/codeGen/CgCallConv.hs index d548741e1f..e4095fd027 100644 --- a/compiler/codeGen/CgCallConv.hs +++ b/compiler/codeGen/CgCallConv.hs @@ -164,7 +164,7 @@ constructSlowCall amodes slowArgs :: DynFlags -> [(CgRep,CmmExpr)] -> [(CgRep,CmmExpr)] slowArgs _ [] = [] slowArgs dflags amodes - | dopt Opt_SccProfilingOn dflags = save_cccs ++ this_pat ++ slowArgs dflags rest + | gopt Opt_SccProfilingOn dflags = save_cccs ++ this_pat ++ slowArgs dflags rest | otherwise = this_pat ++ slowArgs dflags rest where (arg_pat, args, rest) = matchSlowPattern amodes diff --git a/compiler/codeGen/CgCase.lhs b/compiler/codeGen/CgCase.lhs index 0d86319057..595a30e7a1 100644 --- a/compiler/codeGen/CgCase.lhs +++ b/compiler/codeGen/CgCase.lhs @@ -653,7 +653,7 @@ saveCurrentCostCentre :: saveCurrentCostCentre = do dflags <- getDynFlags - if not (dopt Opt_SccProfilingOn dflags) + if not (gopt Opt_SccProfilingOn dflags) then returnFC (Nothing, noStmts) else do slot <- allocPrimStack PtrArg sp_rel <- getSpRelOffset slot diff --git a/compiler/codeGen/CgClosure.lhs b/compiler/codeGen/CgClosure.lhs index 11a5091c07..b5ce231856 100644 --- a/compiler/codeGen/CgClosure.lhs +++ b/compiler/codeGen/CgClosure.lhs @@ -482,8 +482,8 @@ emitBlackHoleCode is_single_entry = do -- Note the eager-blackholing check is here rather than in blackHoleOnEntry, -- because emitBlackHoleCode is called from CmmParse. - let eager_blackholing = not (dopt Opt_SccProfilingOn dflags) - && dopt Opt_EagerBlackHoling dflags + let eager_blackholing = not (gopt Opt_SccProfilingOn dflags) + && gopt Opt_EagerBlackHoling dflags -- Profiling needs slop filling (to support LDV -- profiling), so currently eager blackholing doesn't -- work with profiling. @@ -515,8 +515,8 @@ setupUpdate closure_info code tickyPushUpdateFrame dflags <- getDynFlags if blackHoleOnEntry closure_info && - not (dopt Opt_SccProfilingOn dflags) && - dopt Opt_EagerBlackHoling dflags + not (gopt Opt_SccProfilingOn dflags) && + gopt Opt_EagerBlackHoling dflags then pushBHUpdateFrame (CmmReg nodeReg) code else pushUpdateFrame (CmmReg nodeReg) code diff --git a/compiler/codeGen/CgCon.lhs b/compiler/codeGen/CgCon.lhs index 858de3a616..abb280ff11 100644 --- a/compiler/codeGen/CgCon.lhs +++ b/compiler/codeGen/CgCon.lhs @@ -185,7 +185,7 @@ because they don't support cross package data references well. buildDynCon' dflags platform binder _ con [arg_amode] | maybeIntLikeCon con - , platformOS platform /= OSMinGW32 || not (dopt Opt_PIC dflags) + , platformOS platform /= OSMinGW32 || not (gopt Opt_PIC dflags) , (_, CmmLit (CmmInt val _)) <- arg_amode , let val_int = (fromIntegral val) :: Int , val_int <= mAX_INTLIKE dflags && val_int >= mIN_INTLIKE dflags @@ -197,7 +197,7 @@ buildDynCon' dflags platform binder _ con [arg_amode] buildDynCon' dflags platform binder _ con [arg_amode] | maybeCharLikeCon con - , platformOS platform /= OSMinGW32 || not (dopt Opt_PIC dflags) + , platformOS platform /= OSMinGW32 || not (gopt Opt_PIC dflags) , (_, CmmLit (CmmInt val _)) <- arg_amode , let val_int = (fromIntegral val) :: Int , val_int <= mAX_CHARLIKE dflags && val_int >= mIN_CHARLIKE dflags @@ -324,7 +324,7 @@ cgReturnDataCon con amodes = do if isUnboxedTupleCon con then returnUnboxedTuple amodes -- when profiling we can't shortcut here, we have to enter the closure -- for it to be marked as "used" for LDV profiling. - else if dopt Opt_SccProfilingOn dflags then build_it_then (enter_it dflags) + else if gopt Opt_SccProfilingOn dflags then build_it_then (enter_it dflags) else ASSERT( amodes `lengthIs` dataConRepRepArity con ) do { EndOfBlockInfo _ sequel <- getEndOfBlockInfo ; case sequel of diff --git a/compiler/codeGen/CgExpr.lhs b/compiler/codeGen/CgExpr.lhs index 151947665f..70fb600901 100644 --- a/compiler/codeGen/CgExpr.lhs +++ b/compiler/codeGen/CgExpr.lhs @@ -396,7 +396,7 @@ mkRhsClosure dflags bndr cc bi && all isFollowableArg (map idCgRep fvs) && isUpdatable upd_flag && arity <= mAX_SPEC_AP_SIZE dflags - && not (dopt Opt_SccProfilingOn dflags) + && not (gopt Opt_SccProfilingOn dflags) -- not when profiling: we don't want to -- lose information about this particular -- thunk (e.g. its type) (#949) diff --git a/compiler/codeGen/CgForeignCall.hs b/compiler/codeGen/CgForeignCall.hs index 824a82635d..b0e6516f2d 100644 --- a/compiler/codeGen/CgForeignCall.hs +++ b/compiler/codeGen/CgForeignCall.hs @@ -215,7 +215,7 @@ emitSaveThreadState = do (stack_SP dflags)) stgSp emitCloseNursery -- and save the current cost centre stack in the TSO when profiling: - when (dopt Opt_SccProfilingOn dflags) $ + when (gopt Opt_SccProfilingOn dflags) $ stmtC (CmmStore (cmmOffset dflags stgCurrentTSO (tso_CCCS dflags)) curCCS) -- CurrentNursery->free = Hp+1; @@ -246,7 +246,7 @@ emitLoadThreadState = do ] emitOpenNursery -- and load the current cost centre stack from the TSO when profiling: - when (dopt Opt_SccProfilingOn dflags) $ + when (gopt Opt_SccProfilingOn dflags) $ stmtC $ storeCurCCS $ CmmLoad (cmmOffset dflags (CmmReg (CmmLocal tso)) (tso_CCCS dflags)) (bWord dflags) diff --git a/compiler/codeGen/CgInfoTbls.hs b/compiler/codeGen/CgInfoTbls.hs index 94301af6ef..be16bf6adf 100644 --- a/compiler/codeGen/CgInfoTbls.hs +++ b/compiler/codeGen/CgInfoTbls.hs @@ -74,7 +74,7 @@ mkCmmInfo cl_info cit_prof = prof dflags, cit_srt = closureSRT cl_info }) where - prof dflags | not (dopt Opt_SccProfilingOn dflags) = NoProfilingInfo + prof dflags | not (gopt Opt_SccProfilingOn dflags) = NoProfilingInfo | otherwise = ProfilingInfo ty_descr_w8 val_descr_w8 ty_descr_w8 = stringToWord8s (closureTypeDescr cl_info) val_descr_w8 = stringToWord8s (closureValDescr cl_info) @@ -254,7 +254,7 @@ stdInfoTableSizeW dflags = size_fixed + size_prof where size_fixed = 2 -- layout, type - size_prof | dopt Opt_SccProfilingOn dflags = 2 + size_prof | gopt Opt_SccProfilingOn dflags = 2 | otherwise = 0 stdInfoTableSizeB :: DynFlags -> ByteOff diff --git a/compiler/codeGen/CgParallel.hs b/compiler/codeGen/CgParallel.hs index fdc9846694..0e642cba59 100644 --- a/compiler/codeGen/CgParallel.hs +++ b/compiler/codeGen/CgParallel.hs @@ -40,7 +40,7 @@ doGranAllocate :: CmmExpr -> Code -- macro DO_GRAN_ALLOCATE doGranAllocate _hp = do dflags <- getDynFlags - when (dopt Opt_GranMacros dflags) $ panic "doGranAllocate" + when (gopt Opt_GranMacros dflags) $ panic "doGranAllocate" @@ -52,7 +52,7 @@ granFetchAndReschedule :: [(Id,GlobalReg)] -- Live registers granFetchAndReschedule regs node_reqd = do dflags <- getDynFlags let liveness = mkRegLiveness dflags regs 0 0 - when (dopt Opt_GranMacros dflags && + when (gopt Opt_GranMacros dflags && (node `elem` map snd regs || node_reqd)) $ do fetch reschedule liveness node_reqd @@ -90,7 +90,7 @@ granYield :: [(Id,GlobalReg)] -- Live registers granYield regs node_reqd = do dflags <- getDynFlags let liveness = mkRegLiveness dflags regs 0 0 - when (dopt Opt_GranMacros dflags && node_reqd) $ yield liveness + when (gopt Opt_GranMacros dflags && node_reqd) $ yield liveness yield :: StgWord -> Code yield _liveness = panic "granYield" diff --git a/compiler/codeGen/CgPrimOp.hs b/compiler/codeGen/CgPrimOp.hs index 9e5bc52a79..6185a2b07f 100644 --- a/compiler/codeGen/CgPrimOp.hs +++ b/compiler/codeGen/CgPrimOp.hs @@ -159,7 +159,7 @@ emitPrimOp dflags [res] GetCCSOfOp [arg] _live = stmtC (CmmAssign (CmmLocal res) val) where val - | dopt Opt_SccProfilingOn dflags = costCentreFrom dflags (cmmUntag dflags arg) + | gopt Opt_SccProfilingOn dflags = costCentreFrom dflags (cmmUntag dflags arg) | otherwise = CmmLit (zeroCLit dflags) emitPrimOp _ [res] GetCurrentCCSOp [_dummy_arg] _live diff --git a/compiler/codeGen/CgProf.hs b/compiler/codeGen/CgProf.hs index 03e01b332a..c7ed0d50c3 100644 --- a/compiler/codeGen/CgProf.hs +++ b/compiler/codeGen/CgProf.hs @@ -139,11 +139,11 @@ enterCostCentreFun ccs closure vols = ifProfiling :: Code -> Code ifProfiling code = do dflags <- getDynFlags - if dopt Opt_SccProfilingOn dflags then code else nopC + if gopt Opt_SccProfilingOn dflags then code else nopC ifProfilingL :: DynFlags -> [a] -> [a] ifProfilingL dflags xs - | dopt Opt_SccProfilingOn dflags = xs + | gopt Opt_SccProfilingOn dflags = xs | otherwise = [] -- --------------------------------------------------------------------------- @@ -220,7 +220,7 @@ sizeof_ccs_words dflags emitSetCCC :: CostCentre -> Bool -> Bool -> Code emitSetCCC cc tick push = do dflags <- getDynFlags - if dopt Opt_SccProfilingOn dflags + if gopt Opt_SccProfilingOn dflags then do tmp <- newTemp (bWord dflags) -- TODO FIXME NOW pushCostCentre tmp curCCS cc when tick $ stmtC (bumpSccCount dflags (CmmReg (CmmLocal tmp))) diff --git a/compiler/codeGen/CgTailCall.lhs b/compiler/codeGen/CgTailCall.lhs index 3e64e6007d..b78415fffa 100644 --- a/compiler/codeGen/CgTailCall.lhs +++ b/compiler/codeGen/CgTailCall.lhs @@ -197,7 +197,7 @@ performTailCall fun_info arg_amodes pending_assts -- Test if closure is a constructor maybeSwitchOnCons dflags enterClosure eob | EndOfBlockInfo _ (CaseAlts lbl _ _) <- eob, - not (dopt Opt_SccProfilingOn dflags) + not (gopt Opt_SccProfilingOn dflags) -- we can't shortcut when profiling is on, because we have -- to enter a closure to mark it as "used" for LDV profiling = do { is_constr <- newLabelC diff --git a/compiler/codeGen/CgTicky.hs b/compiler/codeGen/CgTicky.hs index 21837e787b..898d3f0786 100644 --- a/compiler/codeGen/CgTicky.hs +++ b/compiler/codeGen/CgTicky.hs @@ -308,7 +308,7 @@ tickyAllocHeap hp ifTicky :: Code -> Code ifTicky code = do dflags <- getDynFlags - if dopt Opt_Ticky dflags then code + if gopt Opt_Ticky dflags then code else nopC addToMemLbl :: Width -> CLabel -> Int -> CmmStmt diff --git a/compiler/codeGen/ClosureInfo.lhs b/compiler/codeGen/ClosureInfo.lhs index f2cbc21d27..7371ca56a2 100644 --- a/compiler/codeGen/ClosureInfo.lhs +++ b/compiler/codeGen/ClosureInfo.lhs @@ -579,7 +579,7 @@ nodeMustPointToIt _ (LFCon _) = True -- 27/11/92. nodeMustPointToIt dflags (LFThunk _ no_fvs updatable NonStandardThunk _) - = updatable || not no_fvs || dopt Opt_SccProfilingOn dflags + = updatable || not no_fvs || gopt Opt_SccProfilingOn dflags -- For the non-updatable (single-entry case): -- -- True if has fvs (in which case we need access to them, and we @@ -651,7 +651,7 @@ getCallMethod :: DynFlags -> CallMethod getCallMethod dflags _ _ lf_info _ - | nodeMustPointToIt dflags lf_info && dopt Opt_Parallel dflags + | nodeMustPointToIt dflags lf_info && gopt Opt_Parallel dflags = -- If we're parallel, then we must always enter via node. -- The reason is that the closure may have been -- fetched since we allocated it. @@ -666,7 +666,7 @@ getCallMethod dflags name caf (LFReEntrant _ arity _ _) n_args getCallMethod dflags _ _ (LFCon con) n_args -- when profiling, we must always enter a closure when we use it, so -- that the closure can be recorded as used for LDV profiling. - | dopt Opt_SccProfilingOn dflags + | gopt Opt_SccProfilingOn dflags = EnterIt | otherwise = ASSERT( n_args == 0 ) @@ -689,7 +689,7 @@ getCallMethod _dflags _name _caf (LFThunk _ _ _updatable _std_form_info is_fun) -- So the right thing to do is just to enter the thing -- Old version: --- | updatable || dopt Opt_Ticky dflags -- to catch double entry +-- | updatable || gopt Opt_Ticky dflags -- to catch double entry -- = EnterIt -- | otherwise -- Jump direct to code for single-entry thunks -- = JumpToIt (thunkEntryLabel name caf std_form_info updatable) diff --git a/compiler/codeGen/StgCmm.hs b/compiler/codeGen/StgCmm.hs index 67aae3f6c0..944f5aab76 100644 --- a/compiler/codeGen/StgCmm.hs +++ b/compiler/codeGen/StgCmm.hs @@ -262,7 +262,7 @@ cgDataCon data_con maybeExternaliseId :: DynFlags -> Id -> FCode Id maybeExternaliseId dflags id - | dopt Opt_SplitObjs dflags, -- Externalise the name for -split-objs + | gopt Opt_SplitObjs dflags, -- Externalise the name for -split-objs isInternalName name = do { mod <- getModuleName ; returnFC (setIdName id (externalise mod)) } | otherwise = returnFC id diff --git a/compiler/codeGen/StgCmmBind.hs b/compiler/codeGen/StgCmmBind.hs index 5e46dcfd65..439a2aa67e 100644 --- a/compiler/codeGen/StgCmmBind.hs +++ b/compiler/codeGen/StgCmmBind.hs @@ -273,7 +273,7 @@ mkRhsClosure dflags bndr _cc _bi && all (isGcPtrRep . idPrimRep . stripNV) fvs && isUpdatable upd_flag && arity <= mAX_SPEC_AP_SIZE dflags - && not (dopt Opt_SccProfilingOn dflags) + && not (gopt Opt_SccProfilingOn dflags) -- not when profiling: we don't want to -- lose information about this particular -- thunk (e.g. its type) (#949) @@ -574,8 +574,8 @@ emitBlackHoleCode is_single_entry node = do -- Note the eager-blackholing check is here rather than in blackHoleOnEntry, -- because emitBlackHoleCode is called from CmmParse. - let eager_blackholing = not (dopt Opt_SccProfilingOn dflags) - && dopt Opt_EagerBlackHoling dflags + let eager_blackholing = not (gopt Opt_SccProfilingOn dflags) + && gopt Opt_EagerBlackHoling dflags -- Profiling needs slop filling (to support LDV -- profiling), so currently eager blackholing doesn't -- work with profiling. @@ -603,8 +603,8 @@ setupUpdate closure_info node body dflags <- getDynFlags let bh = blackHoleOnEntry closure_info && - not (dopt Opt_SccProfilingOn dflags) && - dopt Opt_EagerBlackHoling dflags + not (gopt Opt_SccProfilingOn dflags) && + gopt Opt_EagerBlackHoling dflags lbl | bh = mkBHUpdInfoLabel | otherwise = mkUpdInfoLabel diff --git a/compiler/codeGen/StgCmmClosure.hs b/compiler/codeGen/StgCmmClosure.hs index f865c37ad8..e4c42d203d 100644 --- a/compiler/codeGen/StgCmmClosure.hs +++ b/compiler/codeGen/StgCmmClosure.hs @@ -400,7 +400,7 @@ nodeMustPointToIt _ (LFCon _) = True -- 27/11/92. nodeMustPointToIt dflags (LFThunk _ no_fvs updatable NonStandardThunk _) - = updatable || not no_fvs || dopt Opt_SccProfilingOn dflags + = updatable || not no_fvs || gopt Opt_SccProfilingOn dflags -- For the non-updatable (single-entry case): -- -- True if has fvs (in which case we need access to them, and we @@ -472,7 +472,7 @@ getCallMethod :: DynFlags -> CallMethod getCallMethod dflags _name _ lf_info _n_args - | nodeMustPointToIt dflags lf_info && dopt Opt_Parallel dflags + | nodeMustPointToIt dflags lf_info && gopt Opt_Parallel dflags = -- If we're parallel, then we must always enter via node. -- The reason is that the closure may have been -- fetched since we allocated it. @@ -496,7 +496,7 @@ getCallMethod dflags name caf (LFThunk _ _ updatable std_form_info is_fun) n_arg -- is the fast-entry code] -- Since is_fun is False, we are *definitely* looking at a data value - | updatable || dopt Opt_Ticky dflags -- to catch double entry + | updatable || gopt Opt_Ticky dflags -- to catch double entry {- 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 @@ -852,7 +852,7 @@ enterIdLabel dflags id c mkProfilingInfo :: DynFlags -> Id -> String -> ProfilingInfo mkProfilingInfo dflags id val_descr - | not (dopt Opt_SccProfilingOn dflags) = NoProfilingInfo + | not (gopt Opt_SccProfilingOn dflags) = NoProfilingInfo | otherwise = ProfilingInfo ty_descr_w8 val_descr_w8 where ty_descr_w8 = stringToWord8s (getTyDescription (idType id)) @@ -899,7 +899,7 @@ mkDataConInfoTable dflags data_con is_static ptr_wds nonptr_wds cl_type = Constr (dataConTagZ data_con) (dataConIdentity data_con) - prof | not (dopt Opt_SccProfilingOn dflags) = NoProfilingInfo + prof | not (gopt Opt_SccProfilingOn dflags) = NoProfilingInfo | otherwise = ProfilingInfo ty_descr val_descr ty_descr = stringToWord8s $ occNameString $ getOccName $ dataConTyCon data_con diff --git a/compiler/codeGen/StgCmmCon.hs b/compiler/codeGen/StgCmmCon.hs index 8e775dec51..ddc6d91d80 100644 --- a/compiler/codeGen/StgCmmCon.hs +++ b/compiler/codeGen/StgCmmCon.hs @@ -181,7 +181,7 @@ because they don't support cross package data references well. buildDynCon' dflags platform binder _cc con [arg] | maybeIntLikeCon con - , platformOS platform /= OSMinGW32 || not (dopt Opt_PIC dflags) + , platformOS platform /= OSMinGW32 || not (gopt Opt_PIC dflags) , StgLitArg (MachInt val) <- arg , val <= fromIntegral (mAX_INTLIKE dflags) -- Comparisons at type Integer! , val >= fromIntegral (mIN_INTLIKE dflags) -- ...ditto... @@ -195,7 +195,7 @@ buildDynCon' dflags platform binder _cc con [arg] buildDynCon' dflags platform binder _cc con [arg] | maybeCharLikeCon con - , platformOS platform /= OSMinGW32 || not (dopt Opt_PIC dflags) + , platformOS platform /= OSMinGW32 || not (gopt Opt_PIC dflags) , StgLitArg (MachChar val) <- arg , let val_int = ord val :: Int , val_int <= mAX_CHARLIKE dflags diff --git a/compiler/codeGen/StgCmmForeign.hs b/compiler/codeGen/StgCmmForeign.hs index 1830f7b6d6..e7925667a8 100644 --- a/compiler/codeGen/StgCmmForeign.hs +++ b/compiler/codeGen/StgCmmForeign.hs @@ -276,7 +276,7 @@ saveThreadState dflags = mkStore (cmmOffset dflags (CmmLoad (cmmOffset dflags stgCurrentTSO (tso_stackobj dflags)) (bWord dflags)) (stack_SP dflags)) stgSp <*> closeNursery dflags -- and save the current cost centre stack in the TSO when profiling: - <*> if dopt Opt_SccProfilingOn dflags then + <*> if gopt Opt_SccProfilingOn dflags then mkStore (cmmOffset dflags stgCurrentTSO (tso_CCCS dflags)) curCCS else mkNop @@ -308,7 +308,7 @@ loadThreadState dflags tso stack = do (rESERVED_STACK_WORDS dflags)), openNursery dflags, -- and load the current cost centre stack from the TSO when profiling: - if dopt Opt_SccProfilingOn dflags then + if gopt Opt_SccProfilingOn dflags then storeCurCCS (CmmLoad (cmmOffset dflags (CmmReg (CmmLocal tso)) (tso_CCCS dflags)) (ccsType dflags)) else mkNop] diff --git a/compiler/codeGen/StgCmmHeap.hs b/compiler/codeGen/StgCmmHeap.hs index c133ab00d4..7393faac9f 100644 --- a/compiler/codeGen/StgCmmHeap.hs +++ b/compiler/codeGen/StgCmmHeap.hs @@ -584,7 +584,7 @@ do_checks mb_stk_hwm checkYield mb_alloc_lit do_gc = do emitAssign hpReg bump_hp emit =<< mkCmmIfThen hp_oflo (alloc_n <*> mkBranch gc_id) else do - when (not (dopt Opt_OmitYields dflags) && checkYield) $ do + when (not (gopt Opt_OmitYields dflags) && checkYield) $ do -- Yielding if HpLim == 0 let yielding = CmmMachOp (mo_wordEq dflags) [CmmReg (CmmGlobal HpLim), diff --git a/compiler/codeGen/StgCmmHpc.hs b/compiler/codeGen/StgCmmHpc.hs index 85f4c161ad..c8e65ad126 100644 --- a/compiler/codeGen/StgCmmHpc.hs +++ b/compiler/codeGen/StgCmmHpc.hs @@ -38,7 +38,7 @@ initHpc _ (NoHpcInfo {}) = return () initHpc this_mod (HpcInfo tickCount _hashNo) = do dflags <- getDynFlags - when (dopt Opt_Hpc dflags) $ + when (gopt Opt_Hpc dflags) $ do emitDataLits (mkHpcTicksLabel this_mod) [ (CmmInt 0 W64) | _ <- take tickCount [0 :: Int ..] diff --git a/compiler/codeGen/StgCmmLayout.hs b/compiler/codeGen/StgCmmLayout.hs index 4742332107..87793ab20f 100644 --- a/compiler/codeGen/StgCmmLayout.hs +++ b/compiler/codeGen/StgCmmLayout.hs @@ -291,7 +291,7 @@ just more arguments that we are passing on the stack (cml_args). slowArgs :: DynFlags -> [(ArgRep, Maybe CmmExpr)] -> [(ArgRep, Maybe CmmExpr)] slowArgs _ [] = [] slowArgs dflags args -- careful: reps contains voids (V), but args does not - | dopt Opt_SccProfilingOn dflags + | gopt Opt_SccProfilingOn dflags = save_cccs ++ this_pat ++ slowArgs dflags rest_args | otherwise = this_pat ++ slowArgs dflags rest_args where @@ -547,7 +547,7 @@ stdInfoTableSizeW dflags = size_fixed + size_prof where size_fixed = 2 -- layout, type - size_prof | dopt Opt_SccProfilingOn dflags = 2 + size_prof | gopt Opt_SccProfilingOn dflags = 2 | otherwise = 0 stdInfoTableSizeB :: DynFlags -> ByteOff diff --git a/compiler/codeGen/StgCmmPrim.hs b/compiler/codeGen/StgCmmPrim.hs index 4e7a48264a..72dd664698 100644 --- a/compiler/codeGen/StgCmmPrim.hs +++ b/compiler/codeGen/StgCmmPrim.hs @@ -240,7 +240,7 @@ emitPrimOp dflags [res] GetCCSOfOp [arg] = emitAssign (CmmLocal res) val where val - | dopt Opt_SccProfilingOn dflags = costCentreFrom dflags (cmmUntag dflags arg) + | gopt Opt_SccProfilingOn dflags = costCentreFrom dflags (cmmUntag dflags arg) | otherwise = CmmLit (zeroCLit dflags) emitPrimOp _ [res] GetCurrentCCSOp [_dummy_arg] diff --git a/compiler/codeGen/StgCmmProf.hs b/compiler/codeGen/StgCmmProf.hs index 1b218462e1..3307604a87 100644 --- a/compiler/codeGen/StgCmmProf.hs +++ b/compiler/codeGen/StgCmmProf.hs @@ -133,7 +133,7 @@ saveCurrentCostCentre :: FCode (Maybe LocalReg) -- Returns Nothing if profiling is off saveCurrentCostCentre = do dflags <- getDynFlags - if not (dopt Opt_SccProfilingOn dflags) + if not (gopt Opt_SccProfilingOn dflags) then return Nothing else do local_cc <- newTemp (ccType dflags) emitAssign (CmmLocal local_cc) curCCS @@ -196,13 +196,13 @@ enterCostCentreFun ccs closure = ifProfiling :: FCode () -> FCode () ifProfiling code = do dflags <- getDynFlags - if dopt Opt_SccProfilingOn dflags + if gopt Opt_SccProfilingOn dflags then code else return () ifProfilingL :: DynFlags -> [a] -> [a] ifProfilingL dflags xs - | dopt Opt_SccProfilingOn dflags = xs + | gopt Opt_SccProfilingOn dflags = xs | otherwise = [] @@ -214,7 +214,7 @@ initCostCentres :: CollectedCCs -> FCode () -- Emit the declarations initCostCentres (local_CCs, ___extern_CCs, singleton_CCSs) = do dflags <- getDynFlags - when (dopt Opt_SccProfilingOn dflags) $ + when (gopt Opt_SccProfilingOn dflags) $ do mapM_ emitCostCentreDecl local_CCs mapM_ emitCostCentreStackDecl singleton_CCSs @@ -280,7 +280,7 @@ sizeof_ccs_words dflags emitSetCCC :: CostCentre -> Bool -> Bool -> FCode () emitSetCCC cc tick push = do dflags <- getDynFlags - if not (dopt Opt_SccProfilingOn dflags) + if not (gopt Opt_SccProfilingOn dflags) then return () else do tmp <- newTemp (ccsType dflags) -- TODO FIXME NOW pushCostCentre tmp curCCS cc diff --git a/compiler/codeGen/StgCmmTicky.hs b/compiler/codeGen/StgCmmTicky.hs index 01babb212f..ffa5168a63 100644 --- a/compiler/codeGen/StgCmmTicky.hs +++ b/compiler/codeGen/StgCmmTicky.hs @@ -332,7 +332,7 @@ tickyAllocHeap hp ifTicky :: FCode () -> FCode () ifTicky code = do dflags <- getDynFlags - if dopt Opt_Ticky dflags then code + if gopt Opt_Ticky dflags then code else return () -- All the ticky-ticky counters are declared "unsigned long" in C |