Skip to content
Snippets Groups Projects
Commit 5d757e5c authored by Edward Z. Yang's avatar Edward Z. Yang Committed by Ian Lynagh
Browse files

Port 'Add two new primops seq# and spark#' (be544179) to new codegen.


Signed-off-by: default avatarEdward Z. Yang <ezyang@mit.edu>
parent 2197a94b
No related branches found
No related tags found
No related merge requests found
......@@ -71,6 +71,10 @@ cgExpr (StgLetNoEscape _ _ binds expr) =
cgExpr (StgCase expr _live_vars _save_vars bndr srt alt_type alts) =
cgCase expr bndr srt alt_type alts
{- seq# a s ==> a -}
cgExpr (StgOpApp (StgPrimOp SeqOp) [StgVarArg a, _] _res_ty) =
cgIdApp a []
cgExpr (StgLam {}) = panic "cgExpr: StgLam"
------------------------------------------------------------------------
......@@ -322,6 +326,22 @@ cgCase scrut@(StgApp v []) _ _ (PrimAlt _) _
; emit $ mkComment $ mkFastString "should be unreachable code"
; emit $ withFreshLabel "l" (\l -> mkLabel l <*> mkBranch l)}
{-
case seq# a s of v
(# s', a' #) -> e
==>
case a of v
(# s', a' #) -> e
(taking advantage of the fact that the return convention for (# State#, a #)
is the same as the return convention for just 'a')
-}
cgCase (StgOpApp (StgPrimOp SeqOp) [StgVarArg a, _] _) bndr srt alt_type alts
= -- handle seq#, same return convention as vanilla 'a'.
cgCase (StgApp a []) bndr srt alt_type alts
cgCase scrut bndr srt alt_type alts
= -- the general case
do { up_hp_usg <- getVirtHp -- Upstream heap usage
......
......@@ -210,6 +210,18 @@ emitPrimOp [res] ParOp [arg]
(CmmLit (CmmLabel (mkCmmCodeLabel rtsPackageId (fsLit "newSpark"))))
[(CmmReg (CmmGlobal BaseReg), AddrHint), (arg,AddrHint)]
emitPrimOp [res] SparkOp [arg]
= do
-- returns the value of arg in res. We're going to therefore
-- refer to arg twice (once to pass to newSpark(), and once to
-- assign to res), so put it in a temporary.
tmp <- assignTemp arg
emitCCall
[]
(CmmLit (CmmLabel (mkCmmCodeLabel rtsPackageId (fsLit "newSpark"))))
[(CmmReg (CmmGlobal BaseReg), AddrHint), ((CmmReg (CmmLocal tmp)), AddrHint)]
emit (mkAssign (CmmLocal res) (CmmReg (CmmLocal tmp)))
emitPrimOp [res] ReadMutVarOp [mutv]
= emit (mkAssign (CmmLocal res) (cmmLoadIndexW mutv fixedHdrSize gcWord))
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment