diff options
author | Isaac Dupree <id@isaac.cedarswampstudios.org> | 2008-01-04 10:53:39 +0000 |
---|---|---|
committer | Isaac Dupree <id@isaac.cedarswampstudios.org> | 2008-01-04 10:53:39 +0000 |
commit | d76b6a05ab36066e8aeb67d58e25992d1ef83a8a (patch) | |
tree | 6a1994b9d1cac97252b4435219b33477cd80e139 /compiler/codeGen | |
parent | 84629bd7dc7377a5f1138df7185a0b9771880834 (diff) | |
download | haskell-d76b6a05ab36066e8aeb67d58e25992d1ef83a8a.tar.gz |
change CmmActual, CmmFormal to use a data CmmHinted rather than tuple (#1405)
This allows the instance of UserOfLocalRegs to be within Haskell98, and IMHO
makes the code a little cleaner generally.
This is one small (though tedious) step towards making GHC's code more
portable...
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 | 23 | ||||
-rw-r--r-- | compiler/codeGen/CgHpc.hs | 10 | ||||
-rw-r--r-- | compiler/codeGen/CgPrimOp.hs | 12 | ||||
-rw-r--r-- | compiler/codeGen/CgProf.hs | 6 | ||||
-rw-r--r-- | compiler/codeGen/CgUtils.hs | 10 |
8 files changed, 36 insertions, 33 deletions
diff --git a/compiler/codeGen/CgCase.lhs b/compiler/codeGen/CgCase.lhs index 398441e30c..beecceb209 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 (zip res_tmps res_hints) fcall args live_in_alts + ; cgForeignCall (zipWith CmmHinted 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 499442fdaa..b7360c8893 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") [(CmmReg nodeReg,PtrHint)] [node] False + ; emitRtsCallWithVols SLIT("newCAF") [CmmHinted (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 bc91bef364..3f1ec45c77 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 = zip arg_tmps (map (typeHint.stgArgType) stg_args) + let arg_hints = zipWith CmmHinted 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 (zip res_regs res_hints) fcall + emitForeignCall (zipWith CmmHinted 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 fec1a8f058..8e1be19beb 100644 --- a/compiler/codeGen/CgForeignCall.hs +++ b/compiler/codeGen/CgForeignCall.hs @@ -64,7 +64,8 @@ cgForeignCall results fcall stg_args live | (stg_arg, (rep,expr)) <- stg_args `zip` reps_n_amodes, nonVoidArg rep] - arg_hints = zip arg_exprs (map (typeHint.stgArgType) stg_args) + arg_hints = zipWith CmmHinted + arg_exprs (map (typeHint.stgArgType) stg_args) -- in emitForeignCall results fcall arg_hints live @@ -72,7 +73,7 @@ cgForeignCall results fcall stg_args live emitForeignCall :: CmmFormals -- where to put the results -> ForeignCall -- the op - -> [(CmmExpr,MachHint)] -- arguments + -> [CmmHinted CmmExpr] -- arguments -> StgLiveVars -- live vars, in case we need to save them -> Code @@ -86,14 +87,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 (fn,_):rest -> (rest, fn) + DynamicTarget -> case args of (CmmHinted 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.fst) args)) + | StdCallConv <- cconv = Just (sum (map (arg_size.cmmExprRep.hintlessCmm) args)) | otherwise = Nothing -- ToDo: this might not be correct for 64-bit API @@ -108,7 +109,7 @@ emitForeignCall' :: Safety -> CmmFormals -- where to put the results -> CmmCallTarget -- the op - -> [(CmmExpr,MachHint)] -- arguments + -> [CmmHinted CmmExpr] -- arguments -> Maybe [GlobalReg] -- live vars, in case we need to save them -> C_SRT -- the SRT of the calls continuation -> CmmReturnInfo @@ -137,13 +138,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) - [ (id,PtrHint) ] - [ (CmmReg (CmmGlobal BaseReg), PtrHint) ] + [ CmmHinted id PtrHint ] + [ CmmHinted (CmmReg (CmmGlobal BaseReg)) PtrHint ] CmmUnsafe ret) stmtC (CmmCall temp_target results temp_args CmmUnsafe ret) stmtC (CmmCall (CmmCallee resumeThread CCallConv) - [ (new_base, PtrHint) ] - [ (CmmReg (CmmLocal id), PtrHint) ] + [ CmmHinted new_base PtrHint ] + [ CmmHinted (CmmReg (CmmLocal id)) PtrHint ] CmmUnsafe ret) -- Assign the result to BaseReg: we -- might now have a different Capability! @@ -163,9 +164,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 (e,hint) = do + where arg_assign_temp (CmmHinted e hint) = do tmp <- maybe_assign_temp e - return (tmp,hint) + return (CmmHinted 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 516a9c7674..cb9c7babde 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 - [(id,NoHint)] + [CmmHinted id NoHint] (CmmCallee (CmmLit $ CmmLabel $ mkForeignLabel mod_alloc Nothing False) CCallConv ) - [ (mkLblExpr mkHpcModuleNameLabel,PtrHint) - , (word32 tickCount, NoHint) - , (word32 hashNo, NoHint) - , (CmmLit $ CmmLabel $ mkHpcTicksLabel $ this_mod,PtrHint) + [ CmmHinted (mkLblExpr mkHpcModuleNameLabel) PtrHint + , CmmHinted (word32 tickCount) NoHint + , CmmHinted (word32 hashNo) NoHint + , CmmHinted (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 a73000c5af..c77e8e5968 100644 --- a/compiler/codeGen/CgPrimOp.hs +++ b/compiler/codeGen/CgPrimOp.hs @@ -123,9 +123,10 @@ emitPrimOp [res] ParOp [arg] live -- later, we might want to inline it. vols <- getVolatileRegs live emitForeignCall' PlayRisky - [(res,NoHint)] + [CmmHinted res NoHint] (CmmCallee newspark CCallConv) - [(CmmReg (CmmGlobal BaseReg), PtrHint), (arg,PtrHint)] + [ (CmmHinted (CmmReg (CmmGlobal BaseReg)) PtrHint) + , (CmmHinted arg PtrHint) ] (Just vols) NoC_SRT -- No SRT b/c we do PlayRisky CmmMayReturn @@ -143,7 +144,8 @@ emitPrimOp [] WriteMutVarOp [mutv,var] live [{-no results-}] (CmmCallee (CmmLit (CmmLabel mkDirty_MUT_VAR_Label)) CCallConv) - [(CmmReg (CmmGlobal BaseReg), PtrHint), (mutv,PtrHint)] + [ (CmmHinted (CmmReg (CmmGlobal BaseReg)) PtrHint) + , (CmmHinted mutv PtrHint) ] (Just vols) NoC_SRT -- No SRT b/c we do PlayRisky CmmMayReturn @@ -348,9 +350,9 @@ emitPrimOp [res] op args live | Just prim <- callishOp op = do vols <- getVolatileRegs live emitForeignCall' PlayRisky - [(res,NoHint)] + [CmmHinted res NoHint] (CmmPrim prim) - [(a,NoHint) | a<-args] -- ToDo: hints? + [CmmHinted 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 6fd6e0165c..c9b82a4679 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") [(stack,PtrHint)] False +enter_ccs_fun stack = emitRtsCall SLIT("EnterFunCCS") [CmmHinted 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") [(ccs,PtrHint), - (CmmLit (mkCCostCentre cc), PtrHint)] + SLIT("PushCostCentre") [CmmHinted ccs PtrHint, + CmmHinted (CmmLit (mkCCostCentre cc)) PtrHint] False bumpSccCount :: CmmExpr -> CmmStmt diff --git a/compiler/codeGen/CgUtils.hs b/compiler/codeGen/CgUtils.hs index 13add6c0bf..adb48cd0d5 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 -> [(CmmExpr,MachHint)] -> Bool -> Code +emitRtsCall :: LitString -> [CmmHinted CmmExpr] -> Bool -> Code emitRtsCall fun args safe = emitRtsCall' [] fun args Nothing safe -- The 'Nothing' says "save all global registers" -emitRtsCallWithVols :: LitString -> [(CmmExpr,MachHint)] -> [GlobalReg] -> Bool -> Code +emitRtsCallWithVols :: LitString -> [CmmHinted CmmExpr] -> [GlobalReg] -> Bool -> Code emitRtsCallWithVols fun args vols safe = emitRtsCall' [] fun args (Just vols) safe emitRtsCallWithResult :: LocalReg -> MachHint -> LitString - -> [(CmmExpr,MachHint)] -> Bool -> Code + -> [CmmHinted CmmExpr] -> Bool -> Code emitRtsCallWithResult res hint fun args safe - = emitRtsCall' [(res,hint)] fun args Nothing safe + = emitRtsCall' [CmmHinted res hint] fun args Nothing safe -- Make a call to an RTS C procedure emitRtsCall' :: CmmFormals -> LitString - -> [(CmmExpr,MachHint)] + -> [CmmHinted CmmExpr] -> Maybe [GlobalReg] -> Bool -- True <=> CmmSafe call -> Code |