diff options
author | Norman Ramsey <nr@eecs.harvard.edu> | 2008-05-03 22:45:14 +0000 |
---|---|---|
committer | Norman Ramsey <nr@eecs.harvard.edu> | 2008-05-03 22:45:14 +0000 |
commit | b71b86cf18374f8011120c92e24ca293986e86ea (patch) | |
tree | 142a818fcd8c3b6549f701246efc844fcdba8f37 /compiler/codeGen | |
parent | 4b0d51372d354687f0b2f7b2c2583bed059ce315 (diff) | |
download | haskell-b71b86cf18374f8011120c92e24ca293986e86ea.tar.gz |
replace Cmm 'hint' with 'kind'
C-- no longer has 'hints'; to guide parameter passing, it
has 'kinds'. Renamed type constructor, data constructor, and record
fields accordingly
Diffstat (limited to 'compiler/codeGen')
-rw-r--r-- | compiler/codeGen/CgCase.lhs | 2 | ||||
-rw-r--r-- | compiler/codeGen/CgClosure.lhs | 2 | ||||
-rw-r--r-- | compiler/codeGen/CgExpr.lhs | 4 | ||||
-rw-r--r-- | compiler/codeGen/CgForeignCall.hs | 22 | ||||
-rw-r--r-- | compiler/codeGen/CgHpc.hs | 10 | ||||
-rw-r--r-- | compiler/codeGen/CgPrimOp.hs | 14 | ||||
-rw-r--r-- | compiler/codeGen/CgProf.hs | 6 | ||||
-rw-r--r-- | compiler/codeGen/CgUtils.hs | 10 |
8 files changed, 35 insertions, 35 deletions
diff --git a/compiler/codeGen/CgCase.lhs b/compiler/codeGen/CgCase.lhs index beecceb209..49c782e12a 100644 --- a/compiler/codeGen/CgCase.lhs +++ b/compiler/codeGen/CgCase.lhs @@ -165,7 +165,7 @@ cgCase (StgOpApp op@(StgFCallOp fcall _) args _) -- exactly like the cgInlinePrimOp case for unboxed tuple alts.. { res_tmps <- mapFCs bindNewToTemp non_void_res_ids ; let res_hints = map (typeHint.idType) non_void_res_ids - ; cgForeignCall (zipWith CmmHinted res_tmps res_hints) fcall args live_in_alts + ; cgForeignCall (zipWith CmmKinded res_tmps res_hints) fcall args live_in_alts ; cgExpr rhs } where (_, res_ids, _, rhs) = head alts diff --git a/compiler/codeGen/CgClosure.lhs b/compiler/codeGen/CgClosure.lhs index 6c8ed29ce2..902b975a91 100644 --- a/compiler/codeGen/CgClosure.lhs +++ b/compiler/codeGen/CgClosure.lhs @@ -560,7 +560,7 @@ link_caf cl_info is_upd = do -- so that the garbage collector can find them -- This must be done *before* the info table pointer is overwritten, -- because the old info table ptr is needed for reversion - ; emitRtsCallWithVols (sLit "newCAF") [CmmHinted (CmmReg nodeReg) PtrHint] [node] False + ; emitRtsCallWithVols (sLit "newCAF") [CmmKinded (CmmReg nodeReg) PtrHint] [node] False -- node is live, so save it. -- Overwrite the closure with a (static) indirection diff --git a/compiler/codeGen/CgExpr.lhs b/compiler/codeGen/CgExpr.lhs index 3f1ec45c77..f22071e2c5 100644 --- a/compiler/codeGen/CgExpr.lhs +++ b/compiler/codeGen/CgExpr.lhs @@ -133,13 +133,13 @@ cgExpr (StgOpApp (StgFCallOp fcall _) stg_args res_ty) = do then assignPtrTemp arg else assignNonPtrTemp arg | (arg, stg_arg) <- arg_exprs] - let arg_hints = zipWith CmmHinted arg_tmps (map (typeHint.stgArgType) stg_args) + let arg_hints = zipWith CmmKinded arg_tmps (map (typeHint.stgArgType) stg_args) {- Now, allocate some result regs. -} (res_reps,res_regs,res_hints) <- newUnboxedTupleRegs res_ty ccallReturnUnboxedTuple (zip res_reps (map (CmmReg . CmmLocal) res_regs)) $ - emitForeignCall (zipWith CmmHinted res_regs res_hints) fcall + emitForeignCall (zipWith CmmKinded res_regs res_hints) fcall arg_hints emptyVarSet{-no live vars-} -- tagToEnum# is special: we need to pull the constructor out of the table, diff --git a/compiler/codeGen/CgForeignCall.hs b/compiler/codeGen/CgForeignCall.hs index ac8e99eafe..b3d779e182 100644 --- a/compiler/codeGen/CgForeignCall.hs +++ b/compiler/codeGen/CgForeignCall.hs @@ -63,7 +63,7 @@ cgForeignCall results fcall stg_args live | (stg_arg, (rep,expr)) <- stg_args `zip` reps_n_amodes, nonVoidArg rep] - arg_hints = zipWith CmmHinted + arg_hints = zipWith CmmKinded arg_exprs (map (typeHint.stgArgType) stg_args) -- in emitForeignCall results fcall arg_hints live @@ -72,7 +72,7 @@ cgForeignCall results fcall stg_args live emitForeignCall :: CmmFormals -- where to put the results -> ForeignCall -- the op - -> [CmmHinted CmmExpr] -- arguments + -> [CmmKinded CmmExpr] -- arguments -> StgLiveVars -- live vars, in case we need to save them -> Code @@ -86,14 +86,14 @@ emitForeignCall results (CCall (CCallSpec target cconv safety)) args live = case target of StaticTarget lbl -> (args, CmmLit (CmmLabel (mkForeignLabel lbl call_size False))) - DynamicTarget -> case args of (CmmHinted fn _):rest -> (rest, fn) + DynamicTarget -> case args of (CmmKinded fn _):rest -> (rest, fn) -- in the stdcall calling convention, the symbol needs @size appended -- to it, where size is the total number of bytes of arguments. We -- attach this info to the CLabel here, and the CLabel pretty printer -- will generate the suffix when the label is printed. call_size - | StdCallConv <- cconv = Just (sum (map (arg_size.cmmExprRep.hintlessCmm) args)) + | StdCallConv <- cconv = Just (sum (map (arg_size.cmmExprRep.kindlessCmm) args)) | otherwise = Nothing -- ToDo: this might not be correct for 64-bit API @@ -108,7 +108,7 @@ emitForeignCall' :: Safety -> CmmFormals -- where to put the results -> CmmCallTarget -- the op - -> [CmmHinted CmmExpr] -- arguments + -> [CmmKinded CmmExpr] -- arguments -> Maybe [GlobalReg] -- live vars, in case we need to save them -> C_SRT -- the SRT of the calls continuation -> CmmReturnInfo @@ -137,13 +137,13 @@ emitForeignCall' safety results target args vols srt ret -- and the CPS will will be the one to convert that -- to this sequence of three CmmUnsafe calls. stmtC (CmmCall (CmmCallee suspendThread CCallConv) - [ CmmHinted id PtrHint ] - [ CmmHinted (CmmReg (CmmGlobal BaseReg)) PtrHint ] + [ CmmKinded id PtrHint ] + [ CmmKinded (CmmReg (CmmGlobal BaseReg)) PtrHint ] CmmUnsafe ret) stmtC (CmmCall temp_target results temp_args CmmUnsafe ret) stmtC (CmmCall (CmmCallee resumeThread CCallConv) - [ CmmHinted new_base PtrHint ] - [ CmmHinted (CmmReg (CmmLocal id)) PtrHint ] + [ CmmKinded new_base PtrHint ] + [ CmmKinded (CmmReg (CmmLocal id)) PtrHint ] CmmUnsafe ret) -- Assign the result to BaseReg: we -- might now have a different Capability! @@ -163,9 +163,9 @@ resumeThread = CmmLit (CmmLabel (mkRtsCodeLabel (sLit "resumeThread"))) -- This is a HACK; really it should be done in the back end, but -- it's easier to generate the temporaries here. load_args_into_temps = mapM arg_assign_temp - where arg_assign_temp (CmmHinted e hint) = do + where arg_assign_temp (CmmKinded e hint) = do tmp <- maybe_assign_temp e - return (CmmHinted tmp hint) + return (CmmKinded tmp hint) load_target_into_temp (CmmCallee expr conv) = do tmp <- maybe_assign_temp expr diff --git a/compiler/codeGen/CgHpc.hs b/compiler/codeGen/CgHpc.hs index cb9c7babde..0d0fdb1183 100644 --- a/compiler/codeGen/CgHpc.hs +++ b/compiler/codeGen/CgHpc.hs @@ -73,15 +73,15 @@ initHpc this_mod (HpcInfo tickCount hashNo) = do { id <- newNonPtrTemp wordRep -- TODO FIXME NOW ; emitForeignCall' PlayRisky - [CmmHinted id NoHint] + [CmmKinded id NoHint] (CmmCallee (CmmLit $ CmmLabel $ mkForeignLabel mod_alloc Nothing False) CCallConv ) - [ CmmHinted (mkLblExpr mkHpcModuleNameLabel) PtrHint - , CmmHinted (word32 tickCount) NoHint - , CmmHinted (word32 hashNo) NoHint - , CmmHinted (CmmLit $ CmmLabel $ mkHpcTicksLabel $ this_mod) PtrHint + [ CmmKinded (mkLblExpr mkHpcModuleNameLabel) PtrHint + , CmmKinded (word32 tickCount) NoHint + , CmmKinded (word32 hashNo) NoHint + , CmmKinded (CmmLit $ CmmLabel $ mkHpcTicksLabel $ this_mod) PtrHint ] (Just []) NoC_SRT -- No SRT b/c we PlayRisky diff --git a/compiler/codeGen/CgPrimOp.hs b/compiler/codeGen/CgPrimOp.hs index 3a3ea12f0e..85a41515e6 100644 --- a/compiler/codeGen/CgPrimOp.hs +++ b/compiler/codeGen/CgPrimOp.hs @@ -122,10 +122,10 @@ emitPrimOp [res] ParOp [arg] live -- later, we might want to inline it. vols <- getVolatileRegs live emitForeignCall' PlayRisky - [CmmHinted res NoHint] + [CmmKinded res NoHint] (CmmCallee newspark CCallConv) - [ (CmmHinted (CmmReg (CmmGlobal BaseReg)) PtrHint) - , (CmmHinted arg PtrHint) ] + [ (CmmKinded (CmmReg (CmmGlobal BaseReg)) PtrHint) + , (CmmKinded arg PtrHint) ] (Just vols) NoC_SRT -- No SRT b/c we do PlayRisky CmmMayReturn @@ -143,8 +143,8 @@ emitPrimOp [] WriteMutVarOp [mutv,var] live [{-no results-}] (CmmCallee (CmmLit (CmmLabel mkDirty_MUT_VAR_Label)) CCallConv) - [ (CmmHinted (CmmReg (CmmGlobal BaseReg)) PtrHint) - , (CmmHinted mutv PtrHint) ] + [ (CmmKinded (CmmReg (CmmGlobal BaseReg)) PtrHint) + , (CmmKinded mutv PtrHint) ] (Just vols) NoC_SRT -- No SRT b/c we do PlayRisky CmmMayReturn @@ -349,9 +349,9 @@ emitPrimOp [res] op args live | Just prim <- callishOp op = do vols <- getVolatileRegs live emitForeignCall' PlayRisky - [CmmHinted res NoHint] + [CmmKinded res NoHint] (CmmPrim prim) - [CmmHinted a NoHint | a<-args] -- ToDo: hints? + [CmmKinded a NoHint | a<-args] -- ToDo: hints? (Just vols) NoC_SRT -- No SRT b/c we do PlayRisky CmmMayReturn diff --git a/compiler/codeGen/CgProf.hs b/compiler/codeGen/CgProf.hs index 4d1fd04c81..c2a8a1bd75 100644 --- a/compiler/codeGen/CgProf.hs +++ b/compiler/codeGen/CgProf.hs @@ -267,7 +267,7 @@ enterCostCentreThunk closure = ifProfiling $ do stmtC $ CmmStore curCCSAddr (costCentreFrom closure) -enter_ccs_fun stack = emitRtsCall (sLit "EnterFunCCS") [CmmHinted stack PtrHint] False +enter_ccs_fun stack = emitRtsCall (sLit "EnterFunCCS") [CmmKinded stack PtrHint] False -- ToDo: vols enter_ccs_fsub = enteringPAP 0 @@ -415,8 +415,8 @@ emitSetCCC cc pushCostCentre :: LocalReg -> CmmExpr -> CostCentre -> Code pushCostCentre result ccs cc = emitRtsCallWithResult result PtrHint - (sLit "PushCostCentre") [CmmHinted ccs PtrHint, - CmmHinted (CmmLit (mkCCostCentre cc)) PtrHint] + (sLit "PushCostCentre") [CmmKinded ccs PtrHint, + CmmKinded (CmmLit (mkCCostCentre cc)) PtrHint] False bumpSccCount :: CmmExpr -> CmmStmt diff --git a/compiler/codeGen/CgUtils.hs b/compiler/codeGen/CgUtils.hs index 3861ddf888..1f44c43ab1 100644 --- a/compiler/codeGen/CgUtils.hs +++ b/compiler/codeGen/CgUtils.hs @@ -333,24 +333,24 @@ emitIfThenElse cond then_part else_part ; labelC join_id } -emitRtsCall :: LitString -> [CmmHinted CmmExpr] -> Bool -> Code +emitRtsCall :: LitString -> [CmmKinded CmmExpr] -> Bool -> Code emitRtsCall fun args safe = emitRtsCall' [] fun args Nothing safe -- The 'Nothing' says "save all global registers" -emitRtsCallWithVols :: LitString -> [CmmHinted CmmExpr] -> [GlobalReg] -> Bool -> Code +emitRtsCallWithVols :: LitString -> [CmmKinded CmmExpr] -> [GlobalReg] -> Bool -> Code emitRtsCallWithVols fun args vols safe = emitRtsCall' [] fun args (Just vols) safe emitRtsCallWithResult :: LocalReg -> MachHint -> LitString - -> [CmmHinted CmmExpr] -> Bool -> Code + -> [CmmKinded CmmExpr] -> Bool -> Code emitRtsCallWithResult res hint fun args safe - = emitRtsCall' [CmmHinted res hint] fun args Nothing safe + = emitRtsCall' [CmmKinded res hint] fun args Nothing safe -- Make a call to an RTS C procedure emitRtsCall' :: CmmFormals -> LitString - -> [CmmHinted CmmExpr] + -> [CmmKinded CmmExpr] -> Maybe [GlobalReg] -> Bool -- True <=> CmmSafe call -> Code |