summaryrefslogtreecommitdiff
path: root/ghc/compiler/nativeGen
diff options
context:
space:
mode:
authorsewardj <unknown>2000-01-24 18:22:08 +0000
committersewardj <unknown>2000-01-24 18:22:08 +0000
commit9ac31f7c4db928dd4ef4ac9719074f64ee02a0d0 (patch)
tree31ca481ac392c4c9b2bf37292992a9281ce263cb /ghc/compiler/nativeGen
parentc81c46d2cdde4d3bb13e1f4d765e43b144ec6716 (diff)
downloadhaskell-9ac31f7c4db928dd4ef4ac9719074f64ee02a0d0.tar.gz
[project @ 2000-01-24 18:22:07 by sewardj]
ARR_HDR_SIZE --> ARR_WORDS_HDR_SIZE, and derived quantities in Constants.h, Constants.lhs et al are similarly renamed. new constant ARR_PTRS_HDR_SIZE, with corresponding derivatives.
Diffstat (limited to 'ghc/compiler/nativeGen')
-rw-r--r--ghc/compiler/nativeGen/Stix.lhs9
-rw-r--r--ghc/compiler/nativeGen/StixInteger.lhs4
-rw-r--r--ghc/compiler/nativeGen/StixPrim.lhs12
3 files changed, 13 insertions, 12 deletions
diff --git a/ghc/compiler/nativeGen/Stix.lhs b/ghc/compiler/nativeGen/Stix.lhs
index 5eb0362ddc..7945f1e51f 100644
--- a/ghc/compiler/nativeGen/Stix.lhs
+++ b/ghc/compiler/nativeGen/Stix.lhs
@@ -10,7 +10,7 @@ module Stix (
stgBaseReg, stgNode, stgSp, stgSu, stgSpLim, stgHp, stgHpLim, stgTagReg,
getUniqLabelNCG,
- fixedHS, arrHS
+ fixedHS, arrWordsHS, arrPtrsHS
) where
#include "HsVersions.h"
@@ -24,7 +24,7 @@ import CLabel ( mkAsmTempLabel, CLabel, pprCLabel, pprCLabel_asm )
import PrimRep ( PrimRep, showPrimRep )
import PrimOp ( PrimOp, pprPrimOp )
import Unique ( Unique )
-import SMRep ( fixedHdrSize, arrHdrSize )
+import SMRep ( fixedHdrSize, arrWordsHdrSize, arrPtrsHdrSize )
import UniqSupply ( returnUs, thenUs, getUniqueUs, UniqSM )
import Outputable
\end{code}
@@ -209,6 +209,7 @@ getUniqLabelNCG
= getUniqueUs `thenUs` \ u ->
returnUs (mkAsmTempLabel u)
-fixedHS = StInt (toInteger fixedHdrSize)
-arrHS = StInt (toInteger arrHdrSize)
+fixedHS = StInt (toInteger fixedHdrSize)
+arrWordsHS = StInt (toInteger arrWordsHdrSize)
+arrPtrsHS = StInt (toInteger arrPtrsHdrSize)
\end{code}
diff --git a/ghc/compiler/nativeGen/StixInteger.lhs b/ghc/compiler/nativeGen/StixInteger.lhs
index 6b9ad9c113..044548c8c4 100644
--- a/ghc/compiler/nativeGen/StixInteger.lhs
+++ b/ghc/compiler/nativeGen/StixInteger.lhs
@@ -22,7 +22,7 @@ import CallConv ( cCallConv )
import OrdList ( OrdList )
import PrimOp ( PrimOp(..) )
import PrimRep ( PrimRep(..) )
-import SMRep ( arrHdrSize )
+import SMRep ( arrWordsHdrSize )
import Stix ( sStLitLbl, StixTree(..), StixTreeList )
import UniqSupply ( returnUs, thenUs, UniqSM )
\end{code}
@@ -139,7 +139,7 @@ toStruct str (alloc,size,arr)
f1 = StAssign IntRep (mpAlloc str) alloc
f2 = StAssign IntRep (mpSize str) size
f3 = StAssign PtrRep (mpData str)
- (StIndex PtrRep arr (StInt (toInteger arrHdrSize)))
+ (StIndex PtrRep arr (StInt (toInteger arrWordsHdrSize)))
in
(f1, f2, f3)
diff --git a/ghc/compiler/nativeGen/StixPrim.lhs b/ghc/compiler/nativeGen/StixPrim.lhs
index ff5332df1a..8508a31f40 100644
--- a/ghc/compiler/nativeGen/StixPrim.lhs
+++ b/ghc/compiler/nativeGen/StixPrim.lhs
@@ -149,7 +149,7 @@ primCode [lhs] ReadArrayOp [obj, ix]
lhs' = amodeToStix lhs
obj' = amodeToStix obj
ix' = amodeToStix ix
- base = StIndex IntRep obj' arrHS
+ base = StIndex IntRep obj' arrPtrsHS
assign = StAssign PtrRep lhs' (StInd PtrRep (StIndex PtrRep base ix'))
in
returnUs (\xs -> assign : xs)
@@ -159,7 +159,7 @@ primCode [] WriteArrayOp [obj, ix, v]
obj' = amodeToStix obj
ix' = amodeToStix ix
v' = amodeToStix v
- base = StIndex IntRep obj' arrHS --(StInt (toInteger 3))
+ base = StIndex IntRep obj' arrPtrsHS
assign = StAssign PtrRep (StInd PtrRep (StIndex PtrRep base ix')) v'
in
returnUs (\xs -> assign : xs)
@@ -174,7 +174,7 @@ primCode [lhs] (ReadByteArrayOp pk) [obj, ix]
lhs' = amodeToStix lhs
obj' = amodeToStix obj
ix' = amodeToStix ix
- base = StIndex IntRep obj' arrHS
+ base = StIndex IntRep obj' arrWordsHS
assign = StAssign pk lhs' (StInd pk (StIndex pk base ix'))
in
returnUs (\xs -> assign : xs)
@@ -203,7 +203,7 @@ primCode [] (WriteByteArrayOp pk) [obj, ix, v]
obj' = amodeToStix obj
ix' = amodeToStix ix
v' = amodeToStix v
- base = StIndex IntRep obj' arrHS
+ base = StIndex IntRep obj' arrWordsHS
assign = StAssign pk (StInd pk (StIndex pk base ix')) v'
in
returnUs (\xs -> assign : xs)
@@ -229,8 +229,8 @@ primCode lhs (CCallOp (Left fn) is_asm may_gc cconv) rhs
let base = amodeToStix' x
in
case getAmodeRep x of
- ArrayRep -> StIndex PtrRep base arrHS
- ByteArrayRep -> StIndex IntRep base arrHS
+ ArrayRep -> StIndex PtrRep base arrPtrsHS
+ ByteArrayRep -> StIndex IntRep base arrWordsHS
ForeignObjRep -> StIndex PtrRep base fixedHS
_ -> base
\end{code}