summaryrefslogtreecommitdiff
path: root/ghc/compiler/codeGen
diff options
context:
space:
mode:
Diffstat (limited to 'ghc/compiler/codeGen')
-rw-r--r--ghc/compiler/codeGen/CgExpr.lhs37
1 files changed, 26 insertions, 11 deletions
diff --git a/ghc/compiler/codeGen/CgExpr.lhs b/ghc/compiler/codeGen/CgExpr.lhs
index 3cc58a675d..ddf179dffe 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.18 1998/12/22 12:55:55 simonm Exp $
+% $Id: CgExpr.lhs,v 1.19 1999/01/14 17:58:46 sof Exp $
%
%********************************************************
%* *
@@ -18,6 +18,7 @@ import Constants ( mAX_SPEC_SELECTEE_SIZE, mAX_SPEC_AP_SIZE )
import StgSyn
import CgMonad
import AbsCSyn
+import AbsCUtils ( mkAbstractCs )
import CLabel ( mkClosureTblLabel )
import SMRep ( fixedHdrSize )
@@ -423,15 +424,29 @@ Little helper for primitives that return unboxed tuples.
\begin{code}
primRetUnboxedTuple :: PrimOp -> [StgArg] -> Type -> Code
primRetUnboxedTuple op args res_ty
- = let (tc,ty_args) = case splitTyConAppThroughNewTypes res_ty of
- Nothing -> pprPanic "primRetUnboxedTuple" (ppr res_ty)
- Just pr -> pr
-
- prim_reps = map typePrimRep ty_args
- temp_uniqs = map mkBuiltinUnique [0..length ty_args]
- temp_amodes = zipWith CTemp temp_uniqs prim_reps
+ = getArgAmodes args `thenFC` \ arg_amodes ->
+ {-
+ put all the arguments in temporaries so they don't get stomped when
+ we push the return address.
+ -}
+ let
+ n_args = length args
+ arg_uniqs = map mkBuiltinUnique [0 .. n_args-1]
+ arg_reps = map getArgPrimRep args
+ arg_temps = zipWith CTemp arg_uniqs arg_reps
+ in
+ absC (mkAbstractCs (zipWith CAssign arg_temps arg_amodes)) `thenC`
+ {-
+ allocate some temporaries for the return values.
+ -}
+ let
+ (tc,ty_args) = case splitTyConAppThroughNewTypes res_ty of
+ Nothing -> pprPanic "primRetUnboxedTuple" (ppr res_ty)
+ Just pr -> pr
+ prim_reps = map typePrimRep ty_args
+ temp_uniqs = map mkBuiltinUnique [ n_args .. n_args + length ty_args - 1]
+ temp_amodes = zipWith CTemp temp_uniqs prim_reps
in
- returnUnboxedTuple temp_amodes
- (getArgAmodes args `thenFC` \ arg_amodes ->
- absC (COpStmt temp_amodes op arg_amodes []))
+ returnUnboxedTuple temp_amodes (absC (COpStmt temp_amodes op arg_temps []))
+
\end{code}