diff --git a/ghc/compiler/codeGen/SMRep.lhs b/ghc/compiler/codeGen/SMRep.lhs
index 0e8f628d3f8ccdb3c0ba84a3917440851f2bc9a5..aabcf404492c5f08867e86a222fa956622bf9ec2 100644
--- a/ghc/compiler/codeGen/SMRep.lhs
+++ b/ghc/compiler/codeGen/SMRep.lhs
@@ -10,7 +10,8 @@ Other modules should access this info through ClosureInfo.
 module SMRep (
 	SMRep(..), ClosureType(..),
 	isConstantRep, isStaticRep,
-	fixedHdrSize, arrHdrSize, fixedItblSize, pprSMRep
+	fixedHdrSize, arrWordsHdrSize, arrPtrsHdrSize,
+        fixedItblSize, pprSMRep
 
 #ifndef OMIT_NATIVE_CODEGEN
 	, getSMRepClosureTypeInt
@@ -50,7 +51,8 @@ module SMRep (
 import CmdLineOpts
 import AbsCSyn		( Liveness(..) )
 import Constants	( sTD_HDR_SIZE, pROF_HDR_SIZE,
-			  gRAN_HDR_SIZE, tICKY_HDR_SIZE, aRR_HDR_SIZE,
+			  gRAN_HDR_SIZE, tICKY_HDR_SIZE, 
+                          aRR_WORDS_HDR_SIZE, aRR_PTRS_HDR_SIZE,
 			  sTD_ITBL_SIZE, pROF_ITBL_SIZE,
 			  gRAN_ITBL_SIZE, tICKY_ITBL_SIZE )
 import Outputable
@@ -111,8 +113,11 @@ tickyHdrSize :: Int{-words-}
 tickyHdrSize | opt_DoTickyProfiling = tICKY_HDR_SIZE
 	     | otherwise	    = 0
 
-arrHdrSize   :: Int{-words-}
-arrHdrSize   = fixedHdrSize + aRR_HDR_SIZE
+arrWordsHdrSize   :: Int{-words-}
+arrWordsHdrSize   = fixedHdrSize + aRR_WORDS_HDR_SIZE
+
+arrPtrsHdrSize   :: Int{-words-}
+arrPtrsHdrSize   = fixedHdrSize + aRR_PTRS_HDR_SIZE
 \end{code}
 
 Size of an info table.
diff --git a/ghc/compiler/main/Constants.lhs b/ghc/compiler/main/Constants.lhs
index 14f466777c57ed56bcdefa905f369f403fae20f4..4a2e0cdfc773bcfe28018ca4fe5b734baad41801 100644
--- a/ghc/compiler/main/Constants.lhs
+++ b/ghc/compiler/main/Constants.lhs
@@ -23,7 +23,8 @@ module Constants (
 	pROF_HDR_SIZE,
 	gRAN_HDR_SIZE,
 	tICKY_HDR_SIZE,
-	aRR_HDR_SIZE,
+	aRR_WORDS_HDR_SIZE,
+	aRR_PTRS_HDR_SIZE,
 
 	sTD_ITBL_SIZE,
 	pROF_ITBL_SIZE,
@@ -196,11 +197,12 @@ mAX_Real_Long_REG       = (0::Int)
 Closure header sizes.
 
 \begin{code}
-sTD_HDR_SIZE   = (STD_HDR_SIZE   :: Int)
-pROF_HDR_SIZE  = (PROF_HDR_SIZE  :: Int)
-gRAN_HDR_SIZE  = (GRAN_HDR_SIZE  :: Int)
-tICKY_HDR_SIZE = (TICKY_HDR_SIZE :: Int)
-aRR_HDR_SIZE   = (ARR_HDR_SIZE   :: Int)
+sTD_HDR_SIZE       = (STD_HDR_SIZE       :: Int)
+pROF_HDR_SIZE      = (PROF_HDR_SIZE      :: Int)
+gRAN_HDR_SIZE      = (GRAN_HDR_SIZE      :: Int)
+tICKY_HDR_SIZE     = (TICKY_HDR_SIZE     :: Int)
+aRR_WORDS_HDR_SIZE = (ARR_WORDS_HDR_SIZE :: Int)
+aRR_PTRS_HDR_SIZE  = (ARR_PTRS_HDR_SIZE  :: Int)
 \end{code}
 
 Info Table sizes.
diff --git a/ghc/compiler/nativeGen/Stix.lhs b/ghc/compiler/nativeGen/Stix.lhs
index 5eb0362ddcc5ac15d4ebce2851b8677d7acf23e4..7945f1e51f22de436f2d092a43c2eb9823d07887 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 6b9ad9c113952ec642ff41c369bad1964eaad8a4..044548c8c481775ffb6a62c94892cb3bc8267ff4 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 ff5332df1ac035bc99912e1561937442a8d80b10..8508a31f40dd6633691b96681c4da061b949a1e0 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}
diff --git a/ghc/includes/Constants.h b/ghc/includes/Constants.h
index 39831969370bf51d306666a572e7096f2148abdc..e0e07b9b736f2985d90ff6761324214a08680907 100644
--- a/ghc/includes/Constants.h
+++ b/ghc/includes/Constants.h
@@ -1,5 +1,5 @@
 /* ----------------------------------------------------------------------------
- * $Id: Constants.h,v 1.8 2000/01/13 14:34:00 hwloidl Exp $
+ * $Id: Constants.h,v 1.9 2000/01/24 18:22:08 sewardj Exp $
  *
  * (c) The GHC Team, 1998-1999
  *
@@ -27,7 +27,8 @@
 #define PAR_HDR_SIZE   0
 #define TICKY_HDR_SIZE 0
 
-#define ARR_HDR_SIZE   1
+#define ARR_WORDS_HDR_SIZE  1
+#define ARR_PTRS_HDR_SIZE   2
 
 /* -----------------------------------------------------------------------------
    Info Table sizes