diff options
author | simonmar <unknown> | 2002-04-29 14:04:11 +0000 |
---|---|---|
committer | simonmar <unknown> | 2002-04-29 14:04:11 +0000 |
commit | b085ee40c7f265a5977ea6ec1c415e573be5ff8c (patch) | |
tree | ab849b59a7eb6a57bc89559706cd71256b5898e4 /ghc/compiler/codeGen | |
parent | f6124b6ca2ec9820f7eb454dbcffbf4b8b790d4f (diff) | |
download | haskell-b085ee40c7f265a5977ea6ec1c415e573be5ff8c.tar.gz |
[project @ 2002-04-29 14:03:38 by simonmar]
FastString cleanup, stage 1.
The FastString type is no longer a mixture of hashed strings and
literal strings, it contains hashed strings only with O(1) comparison
(except for UnicodeStr, but that will also go away in due course). To
create a literal instance of FastString, use FSLIT("..").
By far the most common use of the old literal version of FastString
was in the pattern
ptext SLIT("...")
this combination still works, although it doesn't go via FastString
any more. The next stage will be to remove the need to use this
special combination at all, using a RULE.
To convert a FastString into an SDoc, now use 'ftext' instead of
'ptext'.
I've also removed all the FAST_STRING related macros from HsVersions.h
except for SLIT and FSLIT, just use the relevant functions from
FastString instead.
Diffstat (limited to 'ghc/compiler/codeGen')
-rw-r--r-- | ghc/compiler/codeGen/CgCase.lhs | 8 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgClosure.lhs | 41 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgCon.lhs | 6 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgConTbls.lhs | 6 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgExpr.lhs | 4 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgHeapery.lhs | 8 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgMonad.lhs | 11 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgTailCall.lhs | 12 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgUsages.lhs | 2 | ||||
-rw-r--r-- | ghc/compiler/codeGen/ClosureInfo.lhs | 17 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CodeGen.lhs | 4 |
11 files changed, 61 insertions, 58 deletions
diff --git a/ghc/compiler/codeGen/CgCase.lhs b/ghc/compiler/codeGen/CgCase.lhs index 8201952cd6..df2e165a89 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.56 2001/12/17 12:33:45 simonmar Exp $ +% $Id: CgCase.lhs,v 1.57 2002/04/29 14:03:41 simonmar Exp $ % %******************************************************** %* * @@ -638,14 +638,14 @@ cgSemiTaggedAlts binder alts deflt st_deflt (StgBindDefault _) = Just (Just binder, - (CCallProfCtrMacro SLIT("RET_SEMI_BY_DEFAULT") [], -- ToDo: monadise? + (CCallProfCtrMacro FSLIT("RET_SEMI_BY_DEFAULT") [], -- ToDo: monadise? mkDefaultLabel uniq) ) st_alt (con, args, use_mask, _) = -- Ha! Nothing to do; Node already points to the thing (con_tag, - (CCallProfCtrMacro SLIT("RET_SEMI_IN_HEAP") -- ToDo: monadise? + (CCallProfCtrMacro FSLIT("RET_SEMI_IN_HEAP") -- ToDo: monadise? [mkIntCLit (length args)], -- how big the thing in the heap is join_label) ) @@ -798,7 +798,7 @@ restoreCurrentCostCentre Nothing = returnFC AbsCNop restoreCurrentCostCentre (Just slot) = getSpRelOffset slot `thenFC` \ sp_rel -> freeStackSlots [slot] `thenC` - returnFC (CCallProfCCMacro SLIT("RESTORE_CCCS") [CVal sp_rel CostCentreRep]) + returnFC (CCallProfCCMacro FSLIT("RESTORE_CCCS") [CVal sp_rel CostCentreRep]) -- we use the RESTORE_CCCS macro, rather than just -- assigning into CurCostCentre, in case RESTORE_CCCS -- has some sanity-checking in it. diff --git a/ghc/compiler/codeGen/CgClosure.lhs b/ghc/compiler/codeGen/CgClosure.lhs index e7d70e4fa5..43b4146a56 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.56 2002/03/14 15:27:17 simonpj Exp $ +% $Id: CgClosure.lhs,v 1.57 2002/04/29 14:03:41 simonmar Exp $ % \section[CgClosure]{Code generation for closures} @@ -54,6 +54,7 @@ import PprType ( showTypeCategory ) import Util ( isIn, splitAtList ) import CmdLineOpts ( opt_SccProfilingOn ) import Outputable +import FastString import Name ( nameOccName ) import OccName ( occNameFS ) @@ -262,8 +263,8 @@ closureCodeBody binder_info closure_info cc [] body is_box = case body of { StgApp fun [] -> True; _ -> False } ticky_ent_lit = if (isStaticClosure closure_info) - then SLIT("TICK_ENT_STATIC_THK") - else SLIT("TICK_ENT_DYN_THK") + then FSLIT("TICK_ENT_STATIC_THK") + else FSLIT("TICK_ENT_DYN_THK") body_code = profCtrC ticky_ent_lit [] `thenC` -- node always points when profiling, so this is ok: @@ -372,12 +373,12 @@ closureCodeBody binder_info closure_info cc all_args body fast_entry_code = do mod_name <- moduleName - profCtrC SLIT("TICK_CTR") [ + profCtrC FSLIT("TICK_CTR") [ CLbl ticky_ctr_label DataPtrRep, - mkCString (_PK_ (ppr_for_ticky_name mod_name name)), + mkCString (mkFastString (ppr_for_ticky_name mod_name name)), mkIntCLit stg_arity, -- total # of args mkIntCLit sp_stk_args, -- # passed on stk - mkCString (_PK_ (map (showTypeCategory . idType) all_args)) + mkCString (mkFastString (map (showTypeCategory . idType) all_args)) ] let prof = profCtrC fast_ticky_ent_lit [ @@ -385,8 +386,8 @@ closureCodeBody binder_info closure_info cc all_args body ] -- Nuked for now; see comment at end of file --- CString (_PK_ (show_wrapper_name wrapper_maybe)), --- CString (_PK_ (show_wrapper_arg_kinds wrapper_maybe)) +-- CString (mkFastString (show_wrapper_name wrapper_maybe)), +-- CString (mkFastString (show_wrapper_arg_kinds wrapper_maybe)) -- Bind args to regs/stack as appropriate, and @@ -431,8 +432,8 @@ closureCodeBody binder_info closure_info cc all_args body (slow_ticky_ent_lit, fast_ticky_ent_lit) = if (isStaticClosure closure_info) - then (SLIT("TICK_ENT_STATIC_FUN_STD"), SLIT("TICK_ENT_STATIC_FUN_DIRECT")) - else (SLIT("TICK_ENT_DYN_FUN_STD"), SLIT("TICK_ENT_DYN_FUN_DIRECT")) + then (FSLIT("TICK_ENT_STATIC_FUN_STD"), FSLIT("TICK_ENT_STATIC_FUN_DIRECT")) + else (FSLIT("TICK_ENT_DYN_FUN_STD"), FSLIT("TICK_ENT_DYN_FUN_DIRECT")) stg_arity = length all_args lf_info = closureLFInfo closure_info @@ -481,20 +482,20 @@ enterCostCentreCode closure_info ccs is_thunk is_box if isSubsumedCCS ccs then ASSERT(isToplevClosure closure_info) ASSERT(is_thunk == IsFunction) - costCentresC SLIT("ENTER_CCS_FSUB") [] + costCentresC FSLIT("ENTER_CCS_FSUB") [] else if isDerivedFromCurrentCCS ccs then if re_entrant && not is_box - then costCentresC SLIT("ENTER_CCS_FCL") [CReg node] - else costCentresC SLIT("ENTER_CCS_TCL") [CReg node] + then costCentresC FSLIT("ENTER_CCS_FCL") [CReg node] + else costCentresC FSLIT("ENTER_CCS_TCL") [CReg node] else if isCafCCS ccs then ASSERT(isToplevClosure closure_info) ASSERT(is_thunk == IsThunk) -- might be a PAP, in which case we want to subsume costs if re_entrant - then costCentresC SLIT("ENTER_CCS_FSUB") [] - else costCentresC SLIT("ENTER_CCS_CAF") c_ccs + then costCentresC FSLIT("ENTER_CCS_FSUB") [] + else costCentresC FSLIT("ENTER_CCS_CAF") c_ccs else panic "enterCostCentreCode" @@ -652,7 +653,7 @@ setupUpdate closure_info code code else case (closureUpdReqd closure_info, isStaticClosure closure_info) of - (False,False) -> profCtrC SLIT("TICK_UPDF_OMITTED") [] `thenC` + (False,False) -> profCtrC FSLIT("TICK_UPDF_OMITTED") [] `thenC` code (False,True ) -> (if opt_DoTickyProfiling then @@ -660,16 +661,16 @@ setupUpdate closure_info code link_caf seCafBlackHoleClosureInfo `thenFC` \ _ -> nopC else nopC) `thenC` - profCtrC SLIT("TICK_UPD_CAF_BH_SINGLE_ENTRY") [mkCString cl_name] `thenC` - profCtrC SLIT("TICK_UPDF_OMITTED") [] `thenC` + profCtrC FSLIT("TICK_UPD_CAF_BH_SINGLE_ENTRY") [mkCString cl_name] `thenC` + profCtrC FSLIT("TICK_UPDF_OMITTED") [] `thenC` code (True ,False) -> pushUpdateFrame (CReg node) code (True ,True ) -> -- blackhole the (updatable) CAF: link_caf cafBlackHoleClosureInfo `thenFC` \ update_closure -> - profCtrC SLIT("TICK_UPD_CAF_BH_UPDATABLE") [mkCString cl_name] `thenC` + profCtrC FSLIT("TICK_UPD_CAF_BH_UPDATABLE") [mkCString cl_name] `thenC` pushUpdateFrame update_closure code where - cl_name :: FAST_STRING + cl_name :: FastString cl_name = (occNameFS . nameOccName . closureName) closure_info link_caf :: (ClosureInfo -> ClosureInfo) -- function yielding BH closure_info diff --git a/ghc/compiler/codeGen/CgCon.lhs b/ghc/compiler/codeGen/CgCon.lhs index 3d732636d3..ce9e675e0c 100644 --- a/ghc/compiler/codeGen/CgCon.lhs +++ b/ghc/compiler/codeGen/CgCon.lhs @@ -316,7 +316,7 @@ cgReturnDataCon con amodes temp = CTemp uniq PtrRep in - profCtrC SLIT("TICK_UPD_CON_IN_PLACE") + profCtrC FSLIT("TICK_UPD_CON_IN_PLACE") [mkIntCLit (length amodes)] `thenC` getSpRelOffset args_sp `thenFC` \ sp_rel -> @@ -352,7 +352,7 @@ cgReturnDataCon con amodes let (ret_regs, leftovers) = assignRegs [] (map getAmodeRep amodes) in - profCtrC SLIT("TICK_RET_UNBOXED_TUP") + profCtrC FSLIT("TICK_RET_UNBOXED_TUP") [mkIntCLit (length amodes)] `thenC` doTailCall amodes ret_regs @@ -384,7 +384,7 @@ cgReturnDataCon con amodes -- RETURN - profCtrC SLIT("TICK_RET_NEW") [mkIntCLit (length amodes)] `thenC` + profCtrC FSLIT("TICK_RET_NEW") [mkIntCLit (length amodes)] `thenC` -- could use doTailCall here. performReturn (move_to_reg amode node) return \end{code} diff --git a/ghc/compiler/codeGen/CgConTbls.lhs b/ghc/compiler/codeGen/CgConTbls.lhs index eec28262e6..b61e43380f 100644 --- a/ghc/compiler/codeGen/CgConTbls.lhs +++ b/ghc/compiler/codeGen/CgConTbls.lhs @@ -118,11 +118,11 @@ genConInfo comp_info data_con (static_ci,_) = layOutStaticConstr con_name data_con typePrimRep arg_tys static_body = initC comp_info ( - profCtrC SLIT("TICK_ENT_STATIC_CON") [CReg node] `thenC` + profCtrC FSLIT("TICK_ENT_STATIC_CON") [CReg node] `thenC` ldv_enter_and_body_code) closure_body = initC comp_info ( - profCtrC SLIT("TICK_ENT_DYN_CON") [CReg node] `thenC` + profCtrC FSLIT("TICK_ENT_DYN_CON") [CReg node] `thenC` ldv_enter_and_body_code) ldv_enter_and_body_code = ldvEnter `thenC` body_code @@ -159,7 +159,7 @@ mkConCodeAndInfo con body_code = -- NB: We don't set CC when entering data (WDP 94/06) - profCtrC SLIT("TICK_RET_OLD") + profCtrC FSLIT("TICK_RET_OLD") [mkIntCLit (length arg_things)] `thenC` performReturn AbsCNop -- Ptr to thing already in Node diff --git a/ghc/compiler/codeGen/CgExpr.lhs b/ghc/compiler/codeGen/CgExpr.lhs index c350218ab4..2076a071a4 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.47 2001/11/19 16:34:12 simonpj Exp $ +% $Id: CgExpr.lhs,v 1.48 2002/04/29 14:03:41 simonmar Exp $ % %******************************************************** %* * @@ -257,7 +257,7 @@ centre. cgExpr (StgSCC cc expr) = ASSERT(sccAbleCostCentre cc) costCentresC - SLIT("SET_CCC") + FSLIT("SET_CCC") [mkCCostCentre cc, mkIntCLit (if isSccCountCostCentre cc then 1 else 0)] `thenC` cgExpr expr diff --git a/ghc/compiler/codeGen/CgHeapery.lhs b/ghc/compiler/codeGen/CgHeapery.lhs index ebc51019da..a040d32c00 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.30 2002/02/05 14:39:24 simonpj Exp $ +% $Id: CgHeapery.lhs,v 1.31 2002/04/29 14:03:41 simonmar Exp $ % \section[CgHeapery]{Heap management functions} @@ -118,7 +118,7 @@ fastEntryChecks regs tags ret node_points code = mkAbstractCs [ real_check, if hp == 0 then AbsCNop - else profCtrAbsC SLIT("TICK_ALLOC_HEAP") + else profCtrAbsC FSLIT("TICK_ALLOC_HEAP") [ mkIntCLit hp, CLbl ctr DataPtrRep ] ] @@ -258,7 +258,7 @@ altHeapCheck is_fun regs tags fail_code (Just ret_addr) code then AbsCNop else mkAbstractCs [ checking_code tag_assts, - profCtrAbsC SLIT("TICK_ALLOC_HEAP") + profCtrAbsC FSLIT("TICK_ALLOC_HEAP") [ mkIntCLit words_required, CLbl ctr DataPtrRep ] ] ) `thenC` @@ -317,7 +317,7 @@ altHeapCheck is_fun regs [] AbsCNop Nothing code then AbsCNop else mkAbstractCs [ checking_code, - profCtrAbsC SLIT("TICK_ALLOC_HEAP") + profCtrAbsC FSLIT("TICK_ALLOC_HEAP") [ mkIntCLit words_required, CLbl ctr DataPtrRep ] ] ) `thenC` diff --git a/ghc/compiler/codeGen/CgMonad.lhs b/ghc/compiler/codeGen/CgMonad.lhs index 25c36cd3f5..5c24825a9e 100644 --- a/ghc/compiler/codeGen/CgMonad.lhs +++ b/ghc/compiler/codeGen/CgMonad.lhs @@ -1,7 +1,7 @@ % % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % -% $Id: CgMonad.lhs,v 1.33 2002/01/03 11:44:17 simonmar Exp $ +% $Id: CgMonad.lhs,v 1.34 2002/04/29 14:03:42 simonmar Exp $ % \section[CgMonad]{The code generation monad} @@ -62,6 +62,7 @@ import DataCon ( ConTag ) import Id ( Id ) import VarEnv import PrimRep ( PrimRep(..) ) +import FastString import Outputable infixr 9 `thenC` -- Right-associative! @@ -549,23 +550,23 @@ info (whether SCC profiling or profiling-ctrs going) and possibly emit nothing. \begin{code} -costCentresC :: FAST_STRING -> [CAddrMode] -> Code +costCentresC :: FastString -> [CAddrMode] -> Code costCentresC macro args | opt_SccProfilingOn = absC (CCallProfCCMacro macro args) | otherwise = nopC -profCtrC :: FAST_STRING -> [CAddrMode] -> Code +profCtrC :: FastString -> [CAddrMode] -> Code profCtrC macro args | opt_DoTickyProfiling = absC (CCallProfCtrMacro macro args) | otherwise = nopC -profCtrAbsC :: FAST_STRING -> [CAddrMode] -> AbstractC +profCtrAbsC :: FastString -> [CAddrMode] -> AbstractC profCtrAbsC macro args | opt_DoTickyProfiling = CCallProfCtrMacro macro args | otherwise = AbsCNop ldvEnter :: Code -ldvEnter = costCentresC SLIT("LDV_ENTER") [CReg node] +ldvEnter = costCentresC FSLIT("LDV_ENTER") [CReg node] {- Try to avoid adding too many special compilation strategies here. It's better to modify the header files as necessary for particular diff --git a/ghc/compiler/codeGen/CgTailCall.lhs b/ghc/compiler/codeGen/CgTailCall.lhs index 73e7aaa93f..4468eead66 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.32 2002/03/14 15:27:17 simonpj Exp $ +% $Id: CgTailCall.lhs,v 1.33 2002/04/29 14:03:42 simonmar Exp $ % %******************************************************** %* * @@ -147,7 +147,7 @@ mkStaticAlgReturnCode :: DataCon -- The constructor mkStaticAlgReturnCode con sequel = -- Generate profiling code if necessary (case return_convention of - VectoredReturn sz -> profCtrC SLIT("TICK_VEC_RETURN") [mkIntCLit sz] + VectoredReturn sz -> profCtrC FSLIT("TICK_VEC_RETURN") [mkIntCLit sz] other -> nopC ) `thenC` @@ -226,7 +226,7 @@ mkDynamicAlgReturnCode tycon dyn_tag sequel = case ctrlReturnConvAlg tycon of VectoredReturn sz -> - profCtrC SLIT("TICK_VEC_RETURN") [mkIntCLit sz] `thenC` + profCtrC FSLIT("TICK_VEC_RETURN") [mkIntCLit sz] `thenC` sequelToAmode sequel `thenFC` \ ret_addr -> absC (CReturn ret_addr (DynamicVectoredReturn dyn_tag)) @@ -308,7 +308,7 @@ returnUnboxedTuple amodes before_jump let (ret_regs, leftovers) = assignRegs [] (map getAmodeRep amodes) in - profCtrC SLIT("TICK_RET_UNBOXED_TUP") [mkIntCLit (length amodes)] `thenC` + profCtrC FSLIT("TICK_RET_UNBOXED_TUP") [mkIntCLit (length amodes)] `thenC` doTailCall amodes ret_regs mkUnboxedTupleReturnCode @@ -360,7 +360,7 @@ tailCallFun fun fun_amode lf_info arg_amodes pending_assts = case entry_conv of ViaNode -> ([], - profCtrC SLIT("TICK_ENT_VIA_NODE") [] `thenC` + profCtrC FSLIT("TICK_ENT_VIA_NODE") [] `thenC` absC (CJump (CMacroExpr CodePtrRep ENTRY_CODE [CVal (nodeRel 0) DataPtrRep])) , 0) @@ -518,7 +518,7 @@ doTailCall arg_amodes arg_regs finish_code arity pending_assts enter_jump -- Enter Node (we know infoptr will have the info ptr in it)! = mkAbstractCs [ - CCallProfCtrMacro SLIT("RET_SEMI_FAILED") + CCallProfCtrMacro FSLIT("RET_SEMI_FAILED") [CMacroExpr IntRep INFO_TAG [CReg infoptr]], CJump (CMacroExpr CodePtrRep ENTRY_CODE [CReg infoptr]) ] in diff --git a/ghc/compiler/codeGen/CgUsages.lhs b/ghc/compiler/codeGen/CgUsages.lhs index 8c40c9a470..7030629106 100644 --- a/ghc/compiler/codeGen/CgUsages.lhs +++ b/ghc/compiler/codeGen/CgUsages.lhs @@ -162,7 +162,7 @@ adjustSpAndHp newRealSp = do if (rHp == vHp) then AbsCNop else mkAbstractCs [ CAssign (CReg Hp) (CAddr (hpRel rHp vHp)), - profCtrAbsC SLIT("TICK_ALLOC_HEAP") + profCtrAbsC FSLIT("TICK_ALLOC_HEAP") [ mkIntCLit (vHp - rHp), CLbl ticky_ctr DataPtrRep ] ] let new_usage = ((vSp, fSp, newRealSp, hwSp), (vHp,vHp)) diff --git a/ghc/compiler/codeGen/ClosureInfo.lhs b/ghc/compiler/codeGen/ClosureInfo.lhs index 29d6037c43..5840881330 100644 --- a/ghc/compiler/codeGen/ClosureInfo.lhs +++ b/ghc/compiler/codeGen/ClosureInfo.lhs @@ -1,7 +1,7 @@ % % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % -% $Id: ClosureInfo.lhs,v 1.51 2002/01/02 12:32:19 simonmar Exp $ +% $Id: ClosureInfo.lhs,v 1.52 2002/04/29 14:03:43 simonmar Exp $ % \section[ClosureInfo]{Data structures which describe closures} @@ -90,6 +90,7 @@ import SMRep -- all of it import Type ( isUnLiftedType, Type ) import BasicTypes ( TopLevelFlag(..), isNotTopLevel, isTopLevel ) import Util ( mapAccumL, listLengthCmp, lengthIs ) +import FastString import Outputable \end{code} @@ -999,16 +1000,16 @@ thunkEntryLabel thunk_id _ is_updatable \end{code} \begin{code} -allocProfilingMsg :: ClosureInfo -> FAST_STRING +allocProfilingMsg :: ClosureInfo -> FastString allocProfilingMsg cl_info = case closureLFInfo cl_info of - LFReEntrant _ _ _ _ -> SLIT("TICK_ALLOC_FUN") - LFCon _ _ -> SLIT("TICK_ALLOC_CON") - LFTuple _ _ -> SLIT("TICK_ALLOC_CON") - LFThunk _ _ _ True _ -> SLIT("TICK_ALLOC_UP_THK") -- updatable - LFThunk _ _ _ False _ -> SLIT("TICK_ALLOC_SE_THK") -- nonupdatable - LFBlackHole _ -> SLIT("TICK_ALLOC_BH") + LFReEntrant _ _ _ _ -> FSLIT("TICK_ALLOC_FUN") + LFCon _ _ -> FSLIT("TICK_ALLOC_CON") + LFTuple _ _ -> FSLIT("TICK_ALLOC_CON") + LFThunk _ _ _ True _ -> FSLIT("TICK_ALLOC_UP_THK") -- updatable + LFThunk _ _ _ False _ -> FSLIT("TICK_ALLOC_SE_THK") -- nonupdatable + LFBlackHole _ -> FSLIT("TICK_ALLOC_BH") LFImported -> panic "TICK_ALLOC_IMP" \end{code} diff --git a/ghc/compiler/codeGen/CodeGen.lhs b/ghc/compiler/codeGen/CodeGen.lhs index 5d08357b73..477790d0c1 100644 --- a/ghc/compiler/codeGen/CodeGen.lhs +++ b/ghc/compiler/codeGen/CodeGen.lhs @@ -156,10 +156,10 @@ mkCostCentreStuff (local_CCs, extern_CCs, singleton_CCSs) [ register_ccs, register_cc_stacks ] where mk_register cc - = CCallProfCCMacro SLIT("REGISTER_CC") [mkCCostCentre cc] + = CCallProfCCMacro FSLIT("REGISTER_CC") [mkCCostCentre cc] mk_register_ccs ccs - = CCallProfCCMacro SLIT("REGISTER_CCS") [mkCCostCentreStack ccs] + = CCallProfCCMacro FSLIT("REGISTER_CCS") [mkCCostCentreStack ccs] \end{code} %************************************************************************ |