summaryrefslogtreecommitdiff
path: root/ghc/rts
diff options
context:
space:
mode:
Diffstat (limited to 'ghc/rts')
-rw-r--r--ghc/rts/Assembler.c20
-rw-r--r--ghc/rts/Evaluator.c120
-rw-r--r--ghc/rts/Evaluator.h20
-rw-r--r--ghc/rts/PrimOps.hc88
-rw-r--r--ghc/rts/RtsAPI.c44
-rw-r--r--ghc/rts/RtsUtils.c6
-rw-r--r--ghc/rts/StgMiscClosures.hc36
-rw-r--r--ghc/rts/Updates.hc22
8 files changed, 178 insertions, 178 deletions
diff --git a/ghc/rts/Assembler.c b/ghc/rts/Assembler.c
index e755fdd72f..42ebbc2a75 100644
--- a/ghc/rts/Assembler.c
+++ b/ghc/rts/Assembler.c
@@ -5,8 +5,8 @@
* Copyright (c) 1994-1998.
*
* $RCSfile: Assembler.c,v $
- * $Revision: 1.2 $
- * $Date: 1998/12/02 13:28:09 $
+ * $Revision: 1.3 $
+ * $Date: 1999/01/27 14:51:16 $
*
* This module provides functions to construct BCOs and other closures
* required by the bytecode compiler.
@@ -632,42 +632,42 @@ AsmVar asmBox( AsmBCO bco, AsmRep rep )
switch (rep) {
case CHAR_REP:
asmInstr(bco,i_PACK_CHAR);
- grabHpNonUpd(bco,CZh_sizeW);
+ grabHpNonUpd(bco,Czh_sizeW);
break;
case INT_REP:
asmInstr(bco,i_PACK_INT);
- grabHpNonUpd(bco,IZh_sizeW);
+ grabHpNonUpd(bco,Izh_sizeW);
break;
#ifdef PROVIDE_INT64
case INT64_REP:
asmInstr(bco,i_PACK_INT64);
- grabHpNonUpd(bco,I64Zh_sizeW);
+ grabHpNonUpd(bco,I64zh_sizeW);
break;
#endif
#ifdef PROVIDE_WORD
case WORD_REP:
asmInstr(bco,i_PACK_WORD);
- grabHpNonUpd(bco,WZh_sizeW);
+ grabHpNonUpd(bco,Wzh_sizeW);
break;
#endif
#ifdef PROVIDE_ADDR
case ADDR_REP:
asmInstr(bco,i_PACK_ADDR);
- grabHpNonUpd(bco,AZh_sizeW);
+ grabHpNonUpd(bco,Azh_sizeW);
break;
#endif
case FLOAT_REP:
asmInstr(bco,i_PACK_FLOAT);
- grabHpNonUpd(bco,FZh_sizeW);
+ grabHpNonUpd(bco,Fzh_sizeW);
break;
case DOUBLE_REP:
asmInstr(bco,i_PACK_DOUBLE);
- grabHpNonUpd(bco,DZh_sizeW);
+ grabHpNonUpd(bco,Dzh_sizeW);
break;
#ifdef PROVIDE_STABLE
case STABLE_REP:
asmInstr(bco,i_PACK_STABLE);
- grabHpNonUpd(bco,StableZh_sizeW);
+ grabHpNonUpd(bco,Stablezh_sizeW);
break;
#endif
diff --git a/ghc/rts/Evaluator.c b/ghc/rts/Evaluator.c
index e99a1498d7..36b77edc73 100644
--- a/ghc/rts/Evaluator.c
+++ b/ghc/rts/Evaluator.c
@@ -5,8 +5,8 @@
* Copyright (c) 1994-1998.
*
* $RCSfile: Evaluator.c,v $
- * $Revision: 1.4 $
- * $Date: 1999/01/26 11:12:41 $
+ * $Revision: 1.5 $
+ * $Date: 1999/01/27 14:51:18 $
* ---------------------------------------------------------------------------*/
#include "Rts.h"
@@ -320,7 +320,7 @@ static inline StgPtr grabHpNonUpd( nat size )
/* --------------------------------------------------------------------------
* Manipulate "update frame" list:
* o Update frames (based on stg_do_update and friends in Updates.hc)
- * o Error handling/catching (based on catchZh_fast and friends in Prims.hc)
+ * o Error handling/catching (based on catchzh_fast and friends in Prims.hc)
* o Seq frames (based on seq_frame_entry in Prims.hc)
* o Stop frames
* ------------------------------------------------------------------------*/
@@ -1340,8 +1340,8 @@ enterLoop:
}
case i_PACK_INT:
{
- StgClosure* o = stgCast(StgClosure*,grabHpNonUpd(IZh_sizeW));
- SET_HDR(o,&IZh_con_info,??);
+ StgClosure* o = stgCast(StgClosure*,grabHpNonUpd(Izh_sizeW));
+ SET_HDR(o,&Izh_con_info,??);
payloadWord(o,0) = PopTaggedInt();
IF_DEBUG(evaluator,
fprintf(stderr,"\tBuilt ");
@@ -1385,8 +1385,8 @@ enterLoop:
}
case i_PACK_INT64:
{
- StgClosure* o = stgCast(StgClosure*,grabHpNonUpd(I64Zh_sizeW));
- SET_HDR(o,&I64Zh_con_info,??);
+ StgClosure* o = stgCast(StgClosure*,grabHpNonUpd(I64zh_sizeW));
+ SET_HDR(o,&I64zh_con_info,??);
ASSIGN_Int64(&payloadWord(o,0),PopTaggedInt64());
IF_DEBUG(evaluator,
fprintf(stderr,"\tBuilt ");
@@ -1436,9 +1436,9 @@ enterLoop:
}
case i_PACK_WORD:
{
- StgClosure* o = stgCast(StgClosure*,grabHpNonUpd(WZh_sizeW));
+ StgClosure* o = stgCast(StgClosure*,grabHpNonUpd(Wzh_sizeW));
- SET_HDR(o,&WZh_con_info,??);
+ SET_HDR(o,&Wzh_con_info,??);
payloadWord(o,0) = PopTaggedWord();
IF_DEBUG(evaluator,
fprintf(stderr,"\tBuilt ");
@@ -1473,8 +1473,8 @@ enterLoop:
}
case i_PACK_ADDR:
{
- StgClosure* o = stgCast(StgClosure*,grabHpNonUpd(AZh_sizeW));
- SET_HDR(o,&AZh_con_info,??);
+ StgClosure* o = stgCast(StgClosure*,grabHpNonUpd(Azh_sizeW));
+ SET_HDR(o,&Azh_con_info,??);
payloadPtr(o,0) = PopTaggedAddr();
IF_DEBUG(evaluator,
fprintf(stderr,"\tBuilt ");
@@ -1508,8 +1508,8 @@ enterLoop:
}
case i_PACK_CHAR:
{
- StgClosure* o = stgCast(StgClosure*,grabHpNonUpd(CZh_sizeW));
- SET_HDR(o,&CZh_con_info,??);
+ StgClosure* o = stgCast(StgClosure*,grabHpNonUpd(Czh_sizeW));
+ SET_HDR(o,&Czh_con_info,??);
payloadWord(o,0) = PopTaggedChar();
PushPtr(stgCast(StgPtr,o));
IF_DEBUG(evaluator,
@@ -1542,8 +1542,8 @@ enterLoop:
}
case i_PACK_FLOAT:
{
- StgClosure* o = stgCast(StgClosure*,grabHpNonUpd(FZh_sizeW));
- SET_HDR(o,&FZh_con_info,??);
+ StgClosure* o = stgCast(StgClosure*,grabHpNonUpd(Fzh_sizeW));
+ SET_HDR(o,&Fzh_con_info,??);
ASSIGN_FLT(&payloadWord(o,0),PopTaggedFloat());
IF_DEBUG(evaluator,
fprintf(stderr,"\tBuilt ");
@@ -1576,8 +1576,8 @@ enterLoop:
}
case i_PACK_DOUBLE:
{
- StgClosure* o = stgCast(StgClosure*,grabHpNonUpd(DZh_sizeW));
- SET_HDR(o,&DZh_con_info,??);
+ StgClosure* o = stgCast(StgClosure*,grabHpNonUpd(Dzh_sizeW));
+ SET_HDR(o,&Dzh_con_info,??);
ASSIGN_DBL(&payloadWord(o,0),PopTaggedDouble());
IF_DEBUG(evaluator,
fprintf(stderr,"\tBuilt ");
@@ -1606,7 +1606,7 @@ enterLoop:
}
case i_PACK_STABLE:
{
- StgClosure* o = stgCast(StgClosure*,grabHpNonUpd(StableZh_sizeW));
+ StgClosure* o = stgCast(StgClosure*,grabHpNonUpd(Stablezh_sizeW));
SET_HDR(o,&StablePtr_con_info,??);
payloadWord(o,0) = PopTaggedStablePtr();
IF_DEBUG(evaluator,
@@ -1834,35 +1834,35 @@ enterLoop:
case i_intToAddr: OP_I_A((StgAddr)x); break; /* ToDo */
case i_addrToInt: OP_A_I((StgInt)x); break; /* ToDo */
- case i_indexCharOffAddr: OP_AI_C(indexCharOffAddrZh(r,x,y)); break;
- case i_readCharOffAddr: OP_AI_C(indexCharOffAddrZh(r,x,y)); break;
- case i_writeCharOffAddr: OP_AIC_(writeCharOffAddrZh(x,y,z)); break;
+ case i_indexCharOffAddr: OP_AI_C(indexCharOffAddrzh(r,x,y)); break;
+ case i_readCharOffAddr: OP_AI_C(indexCharOffAddrzh(r,x,y)); break;
+ case i_writeCharOffAddr: OP_AIC_(writeCharOffAddrzh(x,y,z)); break;
- case i_indexIntOffAddr: OP_AI_I(indexIntOffAddrZh(r,x,y)); break;
- case i_readIntOffAddr: OP_AI_I(indexIntOffAddrZh(r,x,y)); break;
- case i_writeIntOffAddr: OP_AII_(writeIntOffAddrZh(x,y,z)); break;
+ case i_indexIntOffAddr: OP_AI_I(indexIntOffAddrzh(r,x,y)); break;
+ case i_readIntOffAddr: OP_AI_I(indexIntOffAddrzh(r,x,y)); break;
+ case i_writeIntOffAddr: OP_AII_(writeIntOffAddrzh(x,y,z)); break;
#ifdef PROVIDE_INT64
- case i_indexInt64OffAddr: OP_AI_z(indexInt64OffAddrZh(r,x,y)); break;
- case i_readInt64OffAddr: OP_AI_z(indexInt64OffAddrZh(r,x,y)); break;
- case i_writeInt64OffAddr: OP_AIz_(writeInt64OffAddrZh(x,y,z)); break;
+ case i_indexInt64OffAddr: OP_AI_z(indexInt64OffAddrzh(r,x,y)); break;
+ case i_readInt64OffAddr: OP_AI_z(indexInt64OffAddrzh(r,x,y)); break;
+ case i_writeInt64OffAddr: OP_AIz_(writeInt64OffAddrzh(x,y,z)); break;
#endif
- case i_indexAddrOffAddr: OP_AI_A(indexAddrOffAddrZh(r,x,y)); break;
- case i_readAddrOffAddr: OP_AI_A(indexAddrOffAddrZh(r,x,y)); break;
- case i_writeAddrOffAddr: OP_AIA_(writeAddrOffAddrZh(x,y,z)); break;
+ case i_indexAddrOffAddr: OP_AI_A(indexAddrOffAddrzh(r,x,y)); break;
+ case i_readAddrOffAddr: OP_AI_A(indexAddrOffAddrzh(r,x,y)); break;
+ case i_writeAddrOffAddr: OP_AIA_(writeAddrOffAddrzh(x,y,z)); break;
- case i_indexFloatOffAddr: OP_AI_F(indexFloatOffAddrZh(r,x,y)); break;
- case i_readFloatOffAddr: OP_AI_F(indexFloatOffAddrZh(r,x,y)); break;
- case i_writeFloatOffAddr: OP_AIF_(writeFloatOffAddrZh(x,y,z)); break;
+ case i_indexFloatOffAddr: OP_AI_F(indexFloatOffAddrzh(r,x,y)); break;
+ case i_readFloatOffAddr: OP_AI_F(indexFloatOffAddrzh(r,x,y)); break;
+ case i_writeFloatOffAddr: OP_AIF_(writeFloatOffAddrzh(x,y,z)); break;
- case i_indexDoubleOffAddr: OP_AI_D(indexDoubleOffAddrZh(r,x,y)); break;
- case i_readDoubleOffAddr: OP_AI_D(indexDoubleOffAddrZh(r,x,y)); break;
- case i_writeDoubleOffAddr: OP_AID_(writeDoubleOffAddrZh(x,y,z)); break;
+ case i_indexDoubleOffAddr: OP_AI_D(indexDoubleOffAddrzh(r,x,y)); break;
+ case i_readDoubleOffAddr: OP_AI_D(indexDoubleOffAddrzh(r,x,y)); break;
+ case i_writeDoubleOffAddr: OP_AID_(writeDoubleOffAddrzh(x,y,z)); break;
#ifdef PROVIDE_STABLE
- case i_indexStableOffAddr: OP_AI_s(indexStablePtrOffAddrZh(r,x,y)); break;
- case i_readStableOffAddr: OP_AI_s(indexStablePtrOffAddrZh(r,x,y)); break;
- case i_writeStableOffAddr: OP_AIs_(writeStablePtrOffAddrZh(x,y,z)); break;
+ case i_indexStableOffAddr: OP_AI_s(indexStablePtrOffAddrzh(r,x,y)); break;
+ case i_readStableOffAddr: OP_AI_s(indexStablePtrOffAddrzh(r,x,y)); break;
+ case i_writeStableOffAddr: OP_AIs_(writeStablePtrOffAddrzh(x,y,z)); break;
#endif
#endif /* PROVIDE_ADDR */
@@ -2263,35 +2263,35 @@ enterLoop:
/* Most of these generate alignment warnings on Sparcs and similar architectures.
* These are harmless and are caused by the cast to C* in BYTE_ARR_CTS.
*/
- case i_indexCharArray: OP_mI_ty(Char,"indexCharArray", indexCharArrayZh(r,x,i)); break;
- case i_readCharArray: OP_mI_ty(Char,"readCharArray", readCharArrayZh(r,x,i)); break;
- case i_writeCharArray: OP_mIty_(Char,"writeCharArray", writeCharArrayZh(x,i,z)); break;
+ case i_indexCharArray: OP_mI_ty(Char,"indexCharArray", indexCharArrayzh(r,x,i)); break;
+ case i_readCharArray: OP_mI_ty(Char,"readCharArray", readCharArrayzh(r,x,i)); break;
+ case i_writeCharArray: OP_mIty_(Char,"writeCharArray", writeCharArrayzh(x,i,z)); break;
- case i_indexIntArray: OP_mI_ty(Int,"indexIntArray", indexIntArrayZh(r,x,i)); break;
- case i_readIntArray: OP_mI_ty(Int,"readIntArray", readIntArrayZh(r,x,i)); break;
- case i_writeIntArray: OP_mIty_(Int,"writeIntArray", writeIntArrayZh(x,i,z)); break;
+ case i_indexIntArray: OP_mI_ty(Int,"indexIntArray", indexIntArrayzh(r,x,i)); break;
+ case i_readIntArray: OP_mI_ty(Int,"readIntArray", readIntArrayzh(r,x,i)); break;
+ case i_writeIntArray: OP_mIty_(Int,"writeIntArray", writeIntArrayzh(x,i,z)); break;
#ifdef PROVIDE_INT64
- case i_indexInt64Array: OP_mI_ty(Int64,"indexInt64Array", indexInt64ArrayZh(r,x,i)); break;
- case i_readInt64Array: OP_mI_ty(Int64,"readInt64Array", readInt64ArrayZh(r,x,i)); break;
- case i_writeInt64Array: OP_mIty_(Int64,"writeInt64Array", writeInt64ArrayZh(x,i,z)); break;
+ case i_indexInt64Array: OP_mI_ty(Int64,"indexInt64Array", indexInt64Arrayzh(r,x,i)); break;
+ case i_readInt64Array: OP_mI_ty(Int64,"readInt64Array", readInt64Arrayzh(r,x,i)); break;
+ case i_writeInt64Array: OP_mIty_(Int64,"writeInt64Array", writeInt64Arrayzh(x,i,z)); break;
#endif
#ifdef PROVIDE_ADDR
- case i_indexAddrArray: OP_mI_ty(Addr,"indexAddrArray", indexAddrArrayZh(r,x,i)); break;
- case i_readAddrArray: OP_mI_ty(Addr,"readAddrArray", readAddrArrayZh(r,x,i)); break;
- case i_writeAddrArray: OP_mIty_(Addr,"writeAddrArray", writeAddrArrayZh(x,i,z)); break;
+ case i_indexAddrArray: OP_mI_ty(Addr,"indexAddrArray", indexAddrArrayzh(r,x,i)); break;
+ case i_readAddrArray: OP_mI_ty(Addr,"readAddrArray", readAddrArrayzh(r,x,i)); break;
+ case i_writeAddrArray: OP_mIty_(Addr,"writeAddrArray", writeAddrArrayzh(x,i,z)); break;
#endif
- case i_indexFloatArray: OP_mI_ty(Float,"indexFloatArray", indexFloatArrayZh(r,x,i)); break;
- case i_readFloatArray: OP_mI_ty(Float,"readFloatArray", readFloatArrayZh(r,x,i)); break;
- case i_writeFloatArray: OP_mIty_(Float,"writeFloatArray", writeFloatArrayZh(x,i,z)); break;
+ case i_indexFloatArray: OP_mI_ty(Float,"indexFloatArray", indexFloatArrayzh(r,x,i)); break;
+ case i_readFloatArray: OP_mI_ty(Float,"readFloatArray", readFloatArrayzh(r,x,i)); break;
+ case i_writeFloatArray: OP_mIty_(Float,"writeFloatArray", writeFloatArrayzh(x,i,z)); break;
- case i_indexDoubleArray: OP_mI_ty(Double,"indexDoubleArray", indexDoubleArrayZh(r,x,i)); break;
- case i_readDoubleArray: OP_mI_ty(Double,"readDoubleArray", readDoubleArrayZh(r,x,i)); break;
- case i_writeDoubleArray: OP_mIty_(Double,"writeDoubleArray", writeDoubleArrayZh(x,i,z)); break;
+ case i_indexDoubleArray: OP_mI_ty(Double,"indexDoubleArray", indexDoubleArrayzh(r,x,i)); break;
+ case i_readDoubleArray: OP_mI_ty(Double,"readDoubleArray", readDoubleArrayzh(r,x,i)); break;
+ case i_writeDoubleArray: OP_mIty_(Double,"writeDoubleArray", writeDoubleArrayzh(x,i,z)); break;
#ifdef PROVIDE_STABLE
- case i_indexStableArray: OP_mI_ty(StablePtr,"indexStableArray", indexStablePtrArrayZh(r,x,i)); break;
- case i_readStableArray: OP_mI_ty(StablePtr,"readStableArray", readStablePtrArrayZh(r,x,i)); break;
- case i_writeStableArray: OP_mIty_(StablePtr,"writeStableArray", writeStablePtrArrayZh(x,i,z)); break;
+ case i_indexStableArray: OP_mI_ty(StablePtr,"indexStableArray", indexStablePtrArrayzh(r,x,i)); break;
+ case i_readStableArray: OP_mI_ty(StablePtr,"readStableArray", readStablePtrArrayzh(r,x,i)); break;
+ case i_writeStableArray: OP_mIty_(StablePtr,"writeStableArray", writeStablePtrArrayzh(x,i,z)); break;
#endif
#endif /* PROVIDE_ARRAY */
diff --git a/ghc/rts/Evaluator.h b/ghc/rts/Evaluator.h
index 05b4a108d3..3f9d735849 100644
--- a/ghc/rts/Evaluator.h
+++ b/ghc/rts/Evaluator.h
@@ -1,5 +1,5 @@
/* -----------------------------------------------------------------------------
- * $Id: Evaluator.h,v 1.2 1998/12/02 13:28:21 simonm Exp $
+ * $Id: Evaluator.h,v 1.3 1999/01/27 14:51:20 simonpj Exp $
*
* Prototypes for functions in Evaluator.c
*
@@ -10,15 +10,15 @@
* (used by Assembler)
* ------------------------------------------------------------------------*/
-#define IZh_sizeW CONSTR_sizeW(0,sizeofW(StgInt))
-#define I64Zh_sizeW CONSTR_sizeW(0,sizeofW(StgInt64))
-#define WZh_sizeW CONSTR_sizeW(0,sizeofW(StgWord))
-#define AZh_sizeW CONSTR_sizeW(0,sizeofW(StgAddr))
-#define CZh_sizeW CONSTR_sizeW(0,sizeofW(StgWord))
-#define FZh_sizeW CONSTR_sizeW(0,sizeofW(StgFloat))
-#define DZh_sizeW CONSTR_sizeW(0,sizeofW(StgDouble))
-#define StableZh_sizeW CONSTR_sizeW(0,sizeofW(StgStablePtr))
-#define GenericZh_sizeW CONSTR_sizeW(1,0)
+#define Izh_sizeW CONSTR_sizeW(0,sizeofW(StgInt))
+#define I64zh_sizeW CONSTR_sizeW(0,sizeofW(StgInt64))
+#define Wzh_sizeW CONSTR_sizeW(0,sizeofW(StgWord))
+#define Azh_sizeW CONSTR_sizeW(0,sizeofW(StgAddr))
+#define Czh_sizeW CONSTR_sizeW(0,sizeofW(StgWord))
+#define Fzh_sizeW CONSTR_sizeW(0,sizeofW(StgFloat))
+#define Dzh_sizeW CONSTR_sizeW(0,sizeofW(StgDouble))
+#define Stablezh_sizeW CONSTR_sizeW(0,sizeofW(StgStablePtr))
+#define Genericzh_sizeW CONSTR_sizeW(1,0)
/* --------------------------------------------------------------------------
*
diff --git a/ghc/rts/PrimOps.hc b/ghc/rts/PrimOps.hc
index 784c6a1676..cfcca50338 100644
--- a/ghc/rts/PrimOps.hc
+++ b/ghc/rts/PrimOps.hc
@@ -1,5 +1,5 @@
/* -----------------------------------------------------------------------------
- * $Id: PrimOps.hc,v 1.8 1999/01/26 16:16:25 simonm Exp $
+ * $Id: PrimOps.hc,v 1.9 1999/01/27 14:51:20 simonpj Exp $
*
* Primitive functions / data
*
@@ -26,8 +26,8 @@
for these.
*/
-W_ GHC_ZcCCallable_static_info[0];
-W_ GHC_ZcCReturnable_static_info[0];
+W_ GHC_ZCCCallable_static_info[0];
+W_ GHC_ZCCReturnable_static_info[0];
#ifndef aix_TARGET_OS /* AIX gives link errors with this as a const (RO assembler section) */
const
@@ -186,12 +186,12 @@ const
#define BYTES_TO_STGWORDS(n) ((n) + sizeof(W_) - 1)/sizeof(W_)
#define newByteArray(ty,scale) \
- FN_(new##ty##ArrayZh_fast) \
+ FN_(new##ty##Arrayzh_fast) \
{ \
W_ stuff_size, size, n; \
StgArrWords* p; \
FB_ \
- MAYBE_GC(NO_PTRS,new##ty##ArrayZh_fast); \
+ MAYBE_GC(NO_PTRS,new##ty##Arrayzh_fast); \
n = R1.w; \
stuff_size = BYTES_TO_STGWORDS(n*scale); \
size = sizeofW(StgArrWords)+ stuff_size; \
@@ -212,7 +212,7 @@ newByteArray(Float, sizeof(StgFloat));
newByteArray(Double, sizeof(StgDouble));
newByteArray(StablePtr, sizeof(StgStablePtr));
-FN_(newArrayZh_fast)
+FN_(newArrayzh_fast)
{
W_ size, n, init;
StgMutArrPtrs* arr;
@@ -220,7 +220,7 @@ FN_(newArrayZh_fast)
FB_
n = R1.w;
- MAYBE_GC(R2_PTR,newArrayZh_fast);
+ MAYBE_GC(R2_PTR,newArrayzh_fast);
size = sizeofW(StgMutArrPtrs) + n;
arr = (StgMutArrPtrs *)RET_STGCALL1(P_, allocate, size);
@@ -240,13 +240,13 @@ FN_(newArrayZh_fast)
FE_
}
-FN_(newMutVarZh_fast)
+FN_(newMutVarzh_fast)
{
StgMutVar* mv;
/* Args: R1.p = initialisation value */
FB_
- HP_CHK_GEN(sizeofW(StgMutVar), R1_PTR, newMutVarZh_fast,);
+ HP_CHK_GEN(sizeofW(StgMutVar), R1_PTR, newMutVarzh_fast,);
TICK_ALLOC_PRIM(sizeofW(StgHeader)+1,1, 0); /* hack, dependent on rep. */
CCS_ALLOC(CCCS,sizeofW(StgMutVar));
@@ -265,14 +265,14 @@ FN_(newMutVarZh_fast)
-------------------------------------------------------------------------- */
#ifndef PAR
-FN_(makeForeignObjZh_fast)
+FN_(makeForeignObjzh_fast)
{
/* R1.p = ptr to foreign object,
*/
StgForeignObj *result;
FB_
- HP_CHK_GEN(sizeofW(StgForeignObj), NO_PTRS, makeForeignObjZh_fast,);
+ HP_CHK_GEN(sizeofW(StgForeignObj), NO_PTRS, makeForeignObjzh_fast,);
TICK_ALLOC_PRIM(sizeofW(StgHeader),
sizeofW(StgForeignObj)-sizeofW(StgHeader), 0);
CCS_ALLOC(CCCS,sizeofW(StgForeignObj)); /* ccs prof */
@@ -294,7 +294,7 @@ FN_(makeForeignObjZh_fast)
#ifndef PAR
-FN_(mkWeakZh_fast)
+FN_(mkWeakzh_fast)
{
/* R1.p = key
R2.p = value
@@ -303,7 +303,7 @@ FN_(mkWeakZh_fast)
StgWeak *w;
FB_
- HP_CHK_GEN(sizeofW(StgWeak), R1_PTR|R2_PTR|R3_PTR, mkWeakZh_fast,);
+ HP_CHK_GEN(sizeofW(StgWeak), R1_PTR|R2_PTR|R3_PTR, mkWeakzh_fast,);
TICK_ALLOC_PRIM(sizeofW(StgHeader)+1, // +1 is for the link field
sizeofW(StgWeak)-sizeofW(StgHeader)-1, 0);
CCS_ALLOC(CCCS,sizeofW(StgWeak)); /* ccs prof */
@@ -324,7 +324,7 @@ FN_(mkWeakZh_fast)
FE_
}
-FN_(deRefWeakZh_fast)
+FN_(deRefWeakzh_fast)
{
/* R1.p = weak ptr
*/
@@ -347,7 +347,7 @@ FN_(deRefWeakZh_fast)
Arbitrary-precision Integer operations.
-------------------------------------------------------------------------- */
-FN_(int2IntegerZh_fast)
+FN_(int2Integerzh_fast)
{
/* arguments: R1 = Int# */
@@ -356,7 +356,7 @@ FN_(int2IntegerZh_fast)
FB_
val = R1.i;
- HP_CHK_GEN(sizeofW(StgArrWords)+1, NO_PTRS, int2IntegerZh_fast,);
+ HP_CHK_GEN(sizeofW(StgArrWords)+1, NO_PTRS, int2Integerzh_fast,);
TICK_ALLOC_PRIM(sizeofW(StgArrWords),1,0);
CCS_ALLOC(CCCS,sizeofW(StgArrWords)+1); /* ccs prof */
@@ -384,7 +384,7 @@ FN_(int2IntegerZh_fast)
FE_
}
-FN_(word2IntegerZh_fast)
+FN_(word2Integerzh_fast)
{
/* arguments: R1 = Word# */
@@ -394,7 +394,7 @@ FN_(word2IntegerZh_fast)
FB_
val = R1.w;
- HP_CHK_GEN(sizeofW(StgArrWords)+1, NO_PTRS, word2IntegerZh_fast,)
+ HP_CHK_GEN(sizeofW(StgArrWords)+1, NO_PTRS, word2Integerzh_fast,)
TICK_ALLOC_PRIM(sizeofW(StgArrWords),1,0);
CCS_ALLOC(CCCS,sizeofW(StgArrWords)+1); /* ccs prof */
@@ -418,13 +418,13 @@ FN_(word2IntegerZh_fast)
FE_
}
-FN_(addr2IntegerZh_fast)
+FN_(addr2Integerzh_fast)
{
MP_INT result;
char *str;
FB_
- MAYBE_GC(NO_PTRS,addr2IntegerZh_fast);
+ MAYBE_GC(NO_PTRS,addr2Integerzh_fast);
/* args: R1 :: Addr# */
str = R1.a;
@@ -445,7 +445,7 @@ FN_(addr2IntegerZh_fast)
#ifdef SUPPORT_LONG_LONGS
-FN_(int64ToIntegerZh_fast)
+FN_(int64ToIntegerzh_fast)
{
/* arguments: L1 = Int64# */
@@ -464,7 +464,7 @@ FN_(int64ToIntegerZh_fast)
/* minimum is one word */
words_needed = 1;
}
- HP_CHK_GEN(sizeofW(StgArrWords)+words_needed, NO_PTRS, int64ToIntegerZh_fast,)
+ HP_CHK_GEN(sizeofW(StgArrWords)+words_needed, NO_PTRS, int64ToIntegerzh_fast,)
TICK_ALLOC_PRIM(sizeofW(StgArrWords),words_needed,0);
CCS_ALLOC(CCCS,sizeofW(StgArrWords)+words_needed); /* ccs prof */
@@ -502,7 +502,7 @@ FN_(int64ToIntegerZh_fast)
FE_
}
-FN_(word64ToIntegerZh_fast)
+FN_(word64ToIntegerzh_fast)
{
/* arguments: L1 = Word64# */
@@ -518,7 +518,7 @@ FN_(word64ToIntegerZh_fast)
} else {
words_needed = 1;
}
- HP_CHK_GEN(sizeofW(StgArrWords)+words_needed, NO_PTRS, word64ToIntegerZh_fast,)
+ HP_CHK_GEN(sizeofW(StgArrWords)+words_needed, NO_PTRS, word64ToIntegerzh_fast,)
TICK_ALLOC_PRIM(sizeofW(StgArrWords),words_needed,0);
CCS_ALLOC(CCCS,sizeofW(StgArrWords)+words_needed); /* ccs prof */
@@ -634,16 +634,16 @@ FN_(name) \
FE_ \
}
-GMP_TAKE2_RET1(plusIntegerZh_fast, mpz_add);
-GMP_TAKE2_RET1(minusIntegerZh_fast, mpz_sub);
-GMP_TAKE2_RET1(timesIntegerZh_fast, mpz_mul);
-GMP_TAKE2_RET1(gcdIntegerZh_fast, mpz_gcd);
+GMP_TAKE2_RET1(plusIntegerzh_fast, mpz_add);
+GMP_TAKE2_RET1(minusIntegerzh_fast, mpz_sub);
+GMP_TAKE2_RET1(timesIntegerzh_fast, mpz_mul);
+GMP_TAKE2_RET1(gcdIntegerzh_fast, mpz_gcd);
-GMP_TAKE2_RET2(quotRemIntegerZh_fast, mpz_tdiv_qr);
-GMP_TAKE2_RET2(divModIntegerZh_fast, mpz_fdiv_qr);
+GMP_TAKE2_RET2(quotRemIntegerzh_fast, mpz_tdiv_qr);
+GMP_TAKE2_RET2(divModIntegerzh_fast, mpz_fdiv_qr);
#ifndef FLOATS_AS_DOUBLES
-FN_(decodeFloatZh_fast)
+FN_(decodeFloatzh_fast)
{
MP_INT mantissa;
I_ exponent;
@@ -654,7 +654,7 @@ FN_(decodeFloatZh_fast)
/* arguments: F1 = Float# */
arg = F1;
- HP_CHK_GEN(sizeof(StgArrWords)+1, NO_PTRS, decodeFloatZh_fast,);
+ HP_CHK_GEN(sizeof(StgArrWords)+1, NO_PTRS, decodeFloatzh_fast,);
TICK_ALLOC_PRIM(sizeofW(StgArrWords),1,0);
CCS_ALLOC(CCCS,sizeofW(StgArrWords)+1); /* ccs prof */
@@ -677,7 +677,7 @@ FN_(decodeFloatZh_fast)
#define DOUBLE_MANTISSA_SIZE (sizeof(StgDouble)/sizeof(W_))
#define ARR_SIZE (sizeof(StgArrWords) + DOUBLE_MANTISSA_SIZE)
-FN_(decodeDoubleZh_fast)
+FN_(decodeDoublezh_fast)
{ MP_INT mantissa;
I_ exponent;
StgDouble arg;
@@ -687,7 +687,7 @@ FN_(decodeDoubleZh_fast)
/* arguments: D1 = Double# */
arg = D1;
- HP_CHK_GEN(ARR_SIZE, NO_PTRS, decodeDoubleZh_fast,);
+ HP_CHK_GEN(ARR_SIZE, NO_PTRS, decodeDoublezh_fast,);
TICK_ALLOC_PRIM(sizeof(StgArrWords),DOUBLE_MANTISSA_SIZE,0);
CCS_ALLOC(CCCS,ARR_SIZE); /* ccs prof */
@@ -710,14 +710,14 @@ FN_(decodeDoubleZh_fast)
* Concurrency primitives
* -------------------------------------------------------------------------- */
-FN_(forkZh_fast)
+FN_(forkzh_fast)
{
FB_
/* args: R1 = closure to spark */
if (closure_SHOULD_SPARK(stgCast(StgClosure*,R1.p))) {
- MAYBE_GC(R1_PTR, forkZh_fast);
+ MAYBE_GC(R1_PTR, forkzh_fast);
/* create it right now, return ThreadID in R1 */
R1.t = RET_STGCALL2(StgTSO *, createIOThread,
@@ -731,7 +731,7 @@ FN_(forkZh_fast)
FE_
}
-FN_(killThreadZh_fast)
+FN_(killThreadzh_fast)
{
FB_
/* args: R1.p = TSO to kill */
@@ -752,14 +752,14 @@ FN_(killThreadZh_fast)
FE_
}
-FN_(newMVarZh_fast)
+FN_(newMVarzh_fast)
{
StgMVar *mvar;
FB_
/* args: none */
- HP_CHK_GEN(sizeofW(StgMVar), NO_PTRS, newMVarZh_fast,);
+ HP_CHK_GEN(sizeofW(StgMVar), NO_PTRS, newMVarzh_fast,);
TICK_ALLOC_PRIM(sizeofW(StgMutVar)-1, // consider head,tail,link as admin wds
1, 0);
CCS_ALLOC(CCCS,sizeofW(StgMVar)); /* ccs prof */
@@ -774,7 +774,7 @@ FN_(newMVarZh_fast)
FE_
}
-FN_(takeMVarZh_fast)
+FN_(takeMVarzh_fast)
{
StgMVar *mvar;
StgClosure *val;
@@ -796,7 +796,7 @@ FN_(takeMVarZh_fast)
CurrentTSO->link = (StgTSO *)&END_TSO_QUEUE_closure;
mvar->tail = CurrentTSO;
- BLOCK(R1_PTR, takeMVarZh_fast);
+ BLOCK(R1_PTR, takeMVarzh_fast);
}
SET_INFO(mvar,&EMPTY_MVAR_info);
@@ -808,7 +808,7 @@ FN_(takeMVarZh_fast)
FE_
}
-FN_(putMVarZh_fast)
+FN_(putMVarzh_fast)
{
StgMVar *mvar;
StgTSO *tso;
@@ -849,13 +849,13 @@ FN_(putMVarZh_fast)
Stable pointer primitives
------------------------------------------------------------------------- */
-FN_(makeStableNameZh_fast)
+FN_(makeStableNamezh_fast)
{
StgWord index;
StgStableName *sn_obj;
FB_
- HP_CHK_GEN(sizeofW(StgStableName), R1_PTR, makeStableNameZh_fast,);
+ HP_CHK_GEN(sizeofW(StgStableName), R1_PTR, makeStableNamezh_fast,);
TICK_ALLOC_PRIM(sizeofW(StgHeader),
sizeofW(StgStableName)-sizeofW(StgHeader), 0);
CCS_ALLOC(CCCS,sizeofW(StgStableName)); /* ccs prof */
diff --git a/ghc/rts/RtsAPI.c b/ghc/rts/RtsAPI.c
index 2ae69a98c5..4cc976d7b0 100644
--- a/ghc/rts/RtsAPI.c
+++ b/ghc/rts/RtsAPI.c
@@ -1,5 +1,5 @@
/* ----------------------------------------------------------------------------
- * $Id: RtsAPI.c,v 1.2 1998/12/02 13:28:38 simonm Exp $
+ * $Id: RtsAPI.c,v 1.3 1999/01/27 14:51:21 simonpj Exp $
*
* API for invoking Haskell functions via the RTS
*
@@ -18,7 +18,7 @@ HaskellObj
rts_mkChar (char c)
{
StgClosure *p = (StgClosure *)allocate(CONSTR_sizeW(0,1));
- p->header.info = &CZh_con_info;
+ p->header.info = &Czh_con_info;
p->payload[0] = (StgClosure *)((StgInt)c);
return p;
}
@@ -27,7 +27,7 @@ HaskellObj
rts_mkInt (int i)
{
StgClosure *p = (StgClosure *)allocate(CONSTR_sizeW(0,1));
- p->header.info = &IZh_con_info;
+ p->header.info = &Izh_con_info;
p->payload[0] = (StgClosure *)(StgInt)i;
return p;
}
@@ -40,7 +40,7 @@ rts_mkInt8 (int i)
instead of the one for Int8, but the types have identical
representation.
*/
- p->header.info = &IZh_con_info;
+ p->header.info = &Izh_con_info;
/* Make sure we mask out the bits above the lowest 8 */
p->payload[0] = (StgClosure *)(StgInt)((unsigned)i & 0xff);
return p;
@@ -54,7 +54,7 @@ rts_mkInt16 (int i)
instead of the one for Int8, but the types have identical
representation.
*/
- p->header.info = &IZh_con_info;
+ p->header.info = &Izh_con_info;
/* Make sure we mask out the relevant bits */
p->payload[0] = (StgClosure *)(StgInt)((unsigned)i & 0xffff);
return p;
@@ -65,7 +65,7 @@ rts_mkInt32 (int i)
{
StgClosure *p = (StgClosure *)allocate(CONSTR_sizeW(0,1));
/* see mk_Int8 comment */
- p->header.info = &IZh_con_info;
+ p->header.info = &Izh_con_info;
p->payload[0] = (StgClosure *)(StgInt)i;
return p;
}
@@ -76,7 +76,7 @@ rts_mkInt64 (long long int i)
long long *tmp;
StgClosure *p = (StgClosure *)allocate(CONSTR_sizeW(0,2));
/* see mk_Int8 comment */
- p->header.info = &I64Zh_con_info;
+ p->header.info = &I64zh_con_info;
tmp = (long long*)&(p->payload[0]);
*tmp = (StgInt64)i;
return p;
@@ -86,7 +86,7 @@ HaskellObj
rts_mkWord (unsigned int i)
{
StgClosure *p = (StgClosure *)allocate(CONSTR_sizeW(0,1));
- p->header.info = &WZh_con_info;
+ p->header.info = &Wzh_con_info;
p->payload[0] = (StgClosure *)(StgWord)i;
return p;
}
@@ -96,7 +96,7 @@ rts_mkWord8 (unsigned int w)
{
/* see rts_mkInt* comments */
StgClosure *p = (StgClosure *)allocate(CONSTR_sizeW(0,1));
- p->header.info = &WZh_con_info;
+ p->header.info = &Wzh_con_info;
p->payload[0] = (StgClosure *)(StgWord)(w & 0xff);
return p;
}
@@ -106,7 +106,7 @@ rts_mkWord16 (unsigned int w)
{
/* see rts_mkInt* comments */
StgClosure *p = (StgClosure *)allocate(CONSTR_sizeW(0,1));
- p->header.info = &WZh_con_info;
+ p->header.info = &Wzh_con_info;
p->payload[0] = (StgClosure *)(StgWord)(w & 0xffff);
return p;
}
@@ -116,7 +116,7 @@ rts_mkWord32 (unsigned int w)
{
/* see rts_mkInt* comments */
StgClosure *p = (StgClosure *)allocate(CONSTR_sizeW(0,1));
- p->header.info = &WZh_con_info;
+ p->header.info = &Wzh_con_info;
p->payload[0] = (StgClosure *)(StgWord)w;
return p;
}
@@ -125,11 +125,11 @@ HaskellObj
rts_mkWord64 (unsigned long long w)
{
unsigned long long *tmp;
- extern StgInfoTable W64Zh_con_info;
+ extern StgInfoTable W64zh_con_info;
StgClosure *p = (StgClosure *)allocate(CONSTR_sizeW(0,2));
/* see mk_Int8 comment */
- p->header.info = &W64Zh_con_info;
+ p->header.info = &W64zh_con_info;
tmp = (unsigned long long*)&(p->payload[0]);
*tmp = (StgNat64)w;
return p;
@@ -139,7 +139,7 @@ HaskellObj
rts_mkFloat (float f)
{
StgClosure *p = (StgClosure *)allocate(CONSTR_sizeW(0,1));
- p->header.info = &FZh_con_info;
+ p->header.info = &Fzh_con_info;
ASSIGN_FLT((P_)p->payload, (StgFloat)f);
return p;
}
@@ -148,7 +148,7 @@ HaskellObj
rts_mkDouble (double d)
{
StgClosure *p = (StgClosure *)allocate(CONSTR_sizeW(0,sizeofW(StgDouble)));
- p->header.info = &DZh_con_info;
+ p->header.info = &Dzh_con_info;
ASSIGN_DBL((P_)p->payload, (StgDouble)d);
return p;
}
@@ -166,7 +166,7 @@ HaskellObj
rts_mkAddr (void *a)
{
StgClosure *p = (StgClosure *)allocate(sizeofW(StgHeader)+1);
- p->header.info = &AZh_con_info;
+ p->header.info = &Azh_con_info;
p->payload[0] = (StgClosure *)a;
return p;
}
@@ -207,7 +207,7 @@ rts_apply (HaskellObj f, HaskellObj arg)
char
rts_getChar (HaskellObj p)
{
- if (p->header.info == &CZh_con_info || p->header.info == &CZh_static_info) {
+ if (p->header.info == &Czh_con_info || p->header.info == &Czh_static_info) {
return (char)(StgWord)(p->payload[0]);
} else {
barf("getChar: not a Char");
@@ -217,7 +217,7 @@ rts_getChar (HaskellObj p)
int
rts_getInt (HaskellObj p)
{
- if (p->header.info == &IZh_con_info || p->header.info == &IZh_static_info) {
+ if (p->header.info == &Izh_con_info || p->header.info == &Izh_static_info) {
return (int)(p->payload[0]);
} else {
barf("getInt: not an Int");
@@ -227,7 +227,7 @@ rts_getInt (HaskellObj p)
unsigned int
rts_getWord (HaskellObj p)
{
- if (p->header.info == &WZh_con_info || p->header.info == &WZh_static_info) {
+ if (p->header.info == &Wzh_con_info || p->header.info == &Wzh_static_info) {
return (unsigned int)(p->payload[0]);
} else {
barf("getWord: not a Word");
@@ -237,7 +237,7 @@ rts_getWord (HaskellObj p)
float
rts_getFloat (HaskellObj p)
{
- if (p->header.info == &FZh_con_info || p->header.info == &FZh_static_info) {
+ if (p->header.info == &Fzh_con_info || p->header.info == &Fzh_static_info) {
return (float)(PK_FLT((P_)p->payload));
} else {
barf("getFloat: not a Float");
@@ -247,7 +247,7 @@ rts_getFloat (HaskellObj p)
double
rts_getDouble (HaskellObj p)
{
- if (p->header.info == &DZh_con_info || p->header.info == &DZh_static_info) {
+ if (p->header.info == &Dzh_con_info || p->header.info == &Dzh_static_info) {
return (double)(PK_DBL((P_)p->payload));
} else {
barf("getDouble: not a Double");
@@ -268,7 +268,7 @@ rts_getStablePtr (HaskellObj p)
void *
rts_getAddr (HaskellObj p)
{
- if (p->header.info == &AZh_con_info || p->header.info == &AZh_static_info) {
+ if (p->header.info == &Azh_con_info || p->header.info == &Azh_static_info) {
return (void *)(p->payload[0]);
} else {
barf("getAddr: not an Addr");
diff --git a/ghc/rts/RtsUtils.c b/ghc/rts/RtsUtils.c
index 2ed09d3315..4361952344 100644
--- a/ghc/rts/RtsUtils.c
+++ b/ghc/rts/RtsUtils.c
@@ -1,5 +1,5 @@
/* -----------------------------------------------------------------------------
- * $Id: RtsUtils.c,v 1.3 1999/01/21 10:31:49 simonm Exp $
+ * $Id: RtsUtils.c,v 1.4 1999/01/27 14:51:21 simonpj Exp $
*
* General utility functions used in the RTS.
*
@@ -160,12 +160,12 @@ nat stg_strlen(char *s)
I_ __GenSymCounter = 0;
I_
-genSymZh(void)
+genSymzh(void)
{
return(__GenSymCounter++);
}
I_
-resetGenSymZh(void) /* it's your funeral */
+resetGenSymzh(void) /* it's your funeral */
{
__GenSymCounter=0;
return(__GenSymCounter);
diff --git a/ghc/rts/StgMiscClosures.hc b/ghc/rts/StgMiscClosures.hc
index 9bc0930131..a5111137a0 100644
--- a/ghc/rts/StgMiscClosures.hc
+++ b/ghc/rts/StgMiscClosures.hc
@@ -1,5 +1,5 @@
/* -----------------------------------------------------------------------------
- * $Id: StgMiscClosures.hc,v 1.8 1999/01/26 11:12:52 simonm Exp $
+ * $Id: StgMiscClosures.hc,v 1.9 1999/01/27 14:51:22 simonpj Exp $
*
* Entry code for various built-in closure types.
*
@@ -407,25 +407,25 @@ VEC_POLY_INFO_TABLE(ret_bco,0, NULL/*srt*/, 0/*srt_off*/, 0/*srt_len*/, RET_BCO)
#ifndef COMPILER
-INFO_TABLE_CONSTR(CZh_con_info,Hugs_CONSTR_entry,0,sizeofW(StgChar),0,CONSTR,const,EF_,0,0);
-INFO_TABLE_CONSTR(IZh_con_info,Hugs_CONSTR_entry,0,sizeofW(StgInt),0,CONSTR,const,EF_,0,0);
-INFO_TABLE_CONSTR(I64Zh_con_info,Hugs_CONSTR_entry,0,sizeofW(StgInt64),0,CONSTR,const,EF_,0,0);
-INFO_TABLE_CONSTR(FZh_con_info,Hugs_CONSTR_entry,0,sizeofW(StgFloat),0,CONSTR,const,EF_,0,0);
-INFO_TABLE_CONSTR(DZh_con_info,Hugs_CONSTR_entry,0,sizeofW(StgDouble),0,CONSTR,const,EF_,0,0);
-INFO_TABLE_CONSTR(AZh_con_info,Hugs_CONSTR_entry,0,sizeofW(StgAddr),0,CONSTR,const,EF_,0,0);
-INFO_TABLE_CONSTR(WZh_con_info,Hugs_CONSTR_entry,0,sizeofW(StgWord),0,CONSTR,const,EF_,0,0);
+INFO_TABLE_CONSTR(Czh_con_info,Hugs_CONSTR_entry,0,sizeofW(StgChar),0,CONSTR,const,EF_,0,0);
+INFO_TABLE_CONSTR(Izh_con_info,Hugs_CONSTR_entry,0,sizeofW(StgInt),0,CONSTR,const,EF_,0,0);
+INFO_TABLE_CONSTR(I64zh_con_info,Hugs_CONSTR_entry,0,sizeofW(StgInt64),0,CONSTR,const,EF_,0,0);
+INFO_TABLE_CONSTR(Fzh_con_info,Hugs_CONSTR_entry,0,sizeofW(StgFloat),0,CONSTR,const,EF_,0,0);
+INFO_TABLE_CONSTR(Dzh_con_info,Hugs_CONSTR_entry,0,sizeofW(StgDouble),0,CONSTR,const,EF_,0,0);
+INFO_TABLE_CONSTR(Azh_con_info,Hugs_CONSTR_entry,0,sizeofW(StgAddr),0,CONSTR,const,EF_,0,0);
+INFO_TABLE_CONSTR(Wzh_con_info,Hugs_CONSTR_entry,0,sizeofW(StgWord),0,CONSTR,const,EF_,0,0);
INFO_TABLE_CONSTR(StablePtr_con_info,Hugs_CONSTR_entry,0,sizeofW(StgStablePtr),0,CONSTR,const,EF_,0,0);
-/* These might seem redundant but {I,C}Zh_static_info are used in
+/* These might seem redundant but {I,C}zh_static_info are used in
* {INT,CHAR}LIKE and the rest are used in RtsAPI.c
*/
-INFO_TABLE_CONSTR(CZh_static_info,Hugs_CONSTR_entry,0,sizeofW(StgChar),0,CONSTR_NOCAF_STATIC,const,EF_,0,0);
-INFO_TABLE_CONSTR(IZh_static_info,Hugs_CONSTR_entry,0,sizeofW(StgInt),0,CONSTR_NOCAF_STATIC,const,EF_,0,0);
-INFO_TABLE_CONSTR(I64Zh_static_info,Hugs_CONSTR_entry,0,sizeofW(StgInt64),0,CONSTR_NOCAF_STATIC,const,EF_,0,0);
-INFO_TABLE_CONSTR(FZh_static_info,Hugs_CONSTR_entry,0,sizeofW(StgFloat),0,CONSTR_NOCAF_STATIC,const,EF_,0,0);
-INFO_TABLE_CONSTR(DZh_static_info,Hugs_CONSTR_entry,0,sizeofW(StgDouble),0,CONSTR_NOCAF_STATIC,const,EF_,0,0);
-INFO_TABLE_CONSTR(AZh_static_info,Hugs_CONSTR_entry,0,sizeofW(StgAddr),0,CONSTR_NOCAF_STATIC,const,EF_,0,0);
-INFO_TABLE_CONSTR(WZh_static_info,Hugs_CONSTR_entry,0,sizeofW(StgWord),0,CONSTR_NOCAF_STATIC,const,EF_,0,0);
+INFO_TABLE_CONSTR(Czh_static_info,Hugs_CONSTR_entry,0,sizeofW(StgChar),0,CONSTR_NOCAF_STATIC,const,EF_,0,0);
+INFO_TABLE_CONSTR(Izh_static_info,Hugs_CONSTR_entry,0,sizeofW(StgInt),0,CONSTR_NOCAF_STATIC,const,EF_,0,0);
+INFO_TABLE_CONSTR(I64zh_static_info,Hugs_CONSTR_entry,0,sizeofW(StgInt64),0,CONSTR_NOCAF_STATIC,const,EF_,0,0);
+INFO_TABLE_CONSTR(Fzh_static_info,Hugs_CONSTR_entry,0,sizeofW(StgFloat),0,CONSTR_NOCAF_STATIC,const,EF_,0,0);
+INFO_TABLE_CONSTR(Dzh_static_info,Hugs_CONSTR_entry,0,sizeofW(StgDouble),0,CONSTR_NOCAF_STATIC,const,EF_,0,0);
+INFO_TABLE_CONSTR(Azh_static_info,Hugs_CONSTR_entry,0,sizeofW(StgAddr),0,CONSTR_NOCAF_STATIC,const,EF_,0,0);
+INFO_TABLE_CONSTR(Wzh_static_info,Hugs_CONSTR_entry,0,sizeofW(StgWord),0,CONSTR_NOCAF_STATIC,const,EF_,0,0);
INFO_TABLE_CONSTR(StablePtr_static_info,Hugs_CONSTR_entry,0,sizeofW(StgStablePtr),0,CONSTR_NOCAF_STATIC,const,EF_,0,0);
#endif /* !defined(COMPILER) */
@@ -440,14 +440,14 @@ INFO_TABLE_CONSTR(StablePtr_static_info,Hugs_CONSTR_entry,0,sizeofW(StgStablePtr
#define CHARLIKE_HDR(n) \
{ \
- STATIC_HDR(CZh_static_info, /* C# */ \
+ STATIC_HDR(Czh_static_info, /* C# */ \
CCS_DONTZuCARE), \
data : n \
}
#define INTLIKE_HDR(n) \
{ \
- STATIC_HDR(IZh_static_info, /* I# */ \
+ STATIC_HDR(Izh_static_info, /* I# */ \
CCS_DONTZuCARE), \
data : n \
}
diff --git a/ghc/rts/Updates.hc b/ghc/rts/Updates.hc
index cbebe92abf..8fc0fae7ed 100644
--- a/ghc/rts/Updates.hc
+++ b/ghc/rts/Updates.hc
@@ -1,5 +1,5 @@
/* -----------------------------------------------------------------------------
- * $Id: Updates.hc,v 1.7 1999/01/21 10:31:53 simonm Exp $
+ * $Id: Updates.hc,v 1.8 1999/01/27 14:51:23 simonpj Exp $
*
* Code to perform updates.
*
@@ -501,8 +501,8 @@ STGFUN(seq_entry)
Exception Primitives
-------------------------------------------------------------------------- */
-FN_(catchZh_fast);
-FN_(raiseZh_fast);
+FN_(catchzh_fast);
+FN_(raisezh_fast);
#define CATCH_FRAME_ENTRY_TEMPLATE(label,ret) \
FN_(label); \
@@ -554,17 +554,17 @@ STGFUN(catch_entry)
FB_
R2.cl = payloadCPtr(R1.cl,1); /* h */
R1.cl = payloadCPtr(R1.cl,0); /* x */
- JMP_(catchZh_fast);
+ JMP_(catchzh_fast);
FE_
}
-FN_(catchZh_fast)
+FN_(catchzh_fast)
{
StgCatchFrame *fp;
FB_
/* args: R1 = m, R2 = k */
- STK_CHK_GEN(sizeofW(StgCatchFrame), R1_PTR | R2_PTR, catchZh_fast, );
+ STK_CHK_GEN(sizeofW(StgCatchFrame), R1_PTR | R2_PTR, catchzh_fast, );
Sp -= sizeofW(StgCatchFrame);
fp = (StgCatchFrame *)Sp;
SET_HDR(fp,(StgInfoTable *)&catch_frame_info,CCCS);
@@ -585,7 +585,7 @@ FN_(catchZh_fast)
*
* raise = {err} \n {} -> raise#{err}
*
- * It is used in raiseZh_fast to update thunks on the update list
+ * It is used in raisezh_fast to update thunks on the update list
* -------------------------------------------------------------------------- */
INFO_TABLE(raise_info,raise_entry,1,0,FUN,const,EF_,0,0);
@@ -593,11 +593,11 @@ STGFUN(raise_entry)
{
FB_
R1.cl = R1.cl->payload[0];
- JMP_(raiseZh_fast);
+ JMP_(raisezh_fast);
FE_
}
-FN_(raiseZh_fast)
+FN_(raisezh_fast)
{
StgClosure *handler;
StgUpdateFrame *p;
@@ -634,10 +634,10 @@ FN_(raiseZh_fast)
break;
case STOP_FRAME:
- barf("raiseZh_fast: STOP_FRAME");
+ barf("raisezh_fast: STOP_FRAME");
default:
- barf("raiseZh_fast: weird activation record");
+ barf("raisezh_fast: weird activation record");
}
break;