summaryrefslogtreecommitdiff
path: root/ghc/includes
diff options
context:
space:
mode:
Diffstat (limited to 'ghc/includes')
-rw-r--r--ghc/includes/MachRegs.h3
-rw-r--r--ghc/includes/PrimOps.h8
-rw-r--r--ghc/includes/Regs.h109
-rw-r--r--ghc/includes/Rts.h6
-rw-r--r--ghc/includes/RtsAPI.h3
-rw-r--r--ghc/includes/SMP.h91
-rw-r--r--ghc/includes/SchedAPI.h7
-rw-r--r--ghc/includes/Stg.h37
-rw-r--r--ghc/includes/StgMacros.h59
-rw-r--r--ghc/includes/StgMiscClosures.h8
-rw-r--r--ghc/includes/StgStorage.h12
-rw-r--r--ghc/includes/Updates.h32
12 files changed, 307 insertions, 68 deletions
diff --git a/ghc/includes/MachRegs.h b/ghc/includes/MachRegs.h
index 35db1c0f28..16d429ad63 100644
--- a/ghc/includes/MachRegs.h
+++ b/ghc/includes/MachRegs.h
@@ -1,5 +1,5 @@
/* -----------------------------------------------------------------------------
- * $Id: MachRegs.h,v 1.5 1999/06/25 09:13:38 simonmar Exp $
+ * $Id: MachRegs.h,v 1.6 1999/11/02 15:05:50 simonmar Exp $
*
* (c) The GHC Team, 1998-1999
*
@@ -206,6 +206,7 @@
#define REG_Base ebx
#endif
#define REG_Sp ebp
+/* #define REG_Su ebx*/
#if STOLEN_X86_REGS >= 3
# define REG_R1 esi
diff --git a/ghc/includes/PrimOps.h b/ghc/includes/PrimOps.h
index 77e74c3d40..0991482276 100644
--- a/ghc/includes/PrimOps.h
+++ b/ghc/includes/PrimOps.h
@@ -1,5 +1,5 @@
/* -----------------------------------------------------------------------------
- * $Id: PrimOps.h,v 1.37 1999/08/25 16:11:43 simonmar Exp $
+ * $Id: PrimOps.h,v 1.38 1999/11/02 15:05:51 simonmar Exp $
*
* (c) The GHC Team, 1998-1999
*
@@ -710,6 +710,12 @@ EF_(forkzh_fast);
EF_(yieldzh_fast);
EF_(killThreadzh_fast);
EF_(seqzh_fast);
+EF_(unblockExceptionszh_fast);
+
+#define blockExceptionszh_fast \
+ if (CurrentTSO->pending_exceptions == NULL) { \
+ CurrentTSO->pending_exceptions = &END_EXCEPTION_LIST_closure; \
+ }
#define myThreadIdzh(t) (t = CurrentTSO)
diff --git a/ghc/includes/Regs.h b/ghc/includes/Regs.h
index df44cc9008..e7a9213ea8 100644
--- a/ghc/includes/Regs.h
+++ b/ghc/includes/Regs.h
@@ -1,5 +1,5 @@
/* -----------------------------------------------------------------------------
- * $Id: Regs.h,v 1.4 1999/03/02 19:44:14 sof Exp $
+ * $Id: Regs.h,v 1.5 1999/11/02 15:05:51 simonmar Exp $
*
* (c) The GHC Team, 1998-1999
*
@@ -25,7 +25,7 @@
* 2) caller-saves registers are saved across a CCall
*/
-typedef struct {
+typedef struct StgRegTable_ {
StgUnion rR1;
StgUnion rR2;
StgUnion rR3;
@@ -48,9 +48,22 @@ typedef struct {
StgPtr rSpLim;
StgPtr rHp;
StgPtr rHpLim;
+ StgTSO *rCurrentTSO;
+ bdescr *rNursery;
+ bdescr *rCurrentNursery;
+#ifdef SMP
+ struct StgRegTable_ *link;
+#endif
} StgRegTable;
+/* No such thing as a MainRegTable under SMP - each thread must
+ * have its own MainRegTable.
+ */
+#ifndef SMP
extern DLL_IMPORT_RTS StgRegTable MainRegTable;
+#endif
+
+#ifdef IN_STG_CODE
/*
* Registers Hp and HpLim are global across the entire system, and are
@@ -85,32 +98,35 @@ extern DLL_IMPORT_RTS StgRegTable MainRegTable;
#define SAVE_Su (CurrentTSO->su)
#define SAVE_SpLim (CurrentTSO->splim)
-#define SAVE_Hp (MainRegTable.rHp)
-#define SAVE_HpLim (MainRegTable.rHpLim)
+#define SAVE_Hp (BaseReg->rHp)
+#define SAVE_HpLim (BaseReg->rHpLim)
+
+#define SAVE_CurrentTSO (BaseReg->rCurrentTSO)
+#define SAVE_CurrentNursery (BaseReg->rCurrentNursery)
/* We sometimes need to save registers across a C-call, eg. if they
* are clobbered in the standard calling convention. We define the
* save locations for all registers in the register table.
*/
-#define SAVE_R1 (MainRegTable.rR1)
-#define SAVE_R2 (MainRegTable.rR2)
-#define SAVE_R3 (MainRegTable.rR3)
-#define SAVE_R4 (MainRegTable.rR4)
-#define SAVE_R5 (MainRegTable.rR5)
-#define SAVE_R6 (MainRegTable.rR6)
-#define SAVE_R7 (MainRegTable.rR7)
-#define SAVE_R8 (MainRegTable.rR8)
+#define SAVE_R1 (BaseReg->rR1)
+#define SAVE_R2 (BaseReg->rR2)
+#define SAVE_R3 (BaseReg->rR3)
+#define SAVE_R4 (BaseReg->rR4)
+#define SAVE_R5 (BaseReg->rR5)
+#define SAVE_R6 (BaseReg->rR6)
+#define SAVE_R7 (BaseReg->rR7)
+#define SAVE_R8 (BaseReg->rR8)
-#define SAVE_F1 (MainRegTable.rF1)
-#define SAVE_F2 (MainRegTable.rF2)
-#define SAVE_F3 (MainRegTable.rF3)
-#define SAVE_F4 (MainRegTable.rF4)
+#define SAVE_F1 (BaseReg->rF1)
+#define SAVE_F2 (BaseReg->rF2)
+#define SAVE_F3 (BaseReg->rF3)
+#define SAVE_F4 (BaseReg->rF4)
-#define SAVE_D1 (MainRegTable.rD1)
-#define SAVE_D2 (MainRegTable.rD2)
+#define SAVE_D1 (BaseReg->rD1)
+#define SAVE_D2 (BaseReg->rD2)
-#define SAVE_L1 (MainRegTable.rL1)
+#define SAVE_L1 (BaseReg->rL1)
/* -----------------------------------------------------------------------------
* Emit the GCC-specific register declarations for each machine
@@ -240,6 +256,9 @@ GLOBAL_REG_DECL(StgWord64,L1,REG_L1)
#ifdef REG_Base
GLOBAL_REG_DECL(StgRegTable *,BaseReg,REG_Base)
#else
+#ifdef SMP
+#error BaseReg must be in a register for SMP
+#endif
#define BaseReg (&MainRegTable)
#endif
@@ -273,6 +292,18 @@ GLOBAL_REG_DECL(P_,HpLim,REG_HpLim)
#define HpLim (BaseReg->rHpLim)
#endif
+#ifdef REG_CurrentTSO
+GLOBAL_REG_DECL(StgTSO *,CurrentTSO,REG_CurrentTSO)
+#else
+#define CurrentTSO (BaseReg->rCurrentTSO)
+#endif
+
+#ifdef REG_CurrentNursery
+GLOBAL_REG_DECL(bdescr *,CurrentNursery,REG_CurrentNursery)
+#else
+#define CurrentNursery (BaseReg->rCurrentNursery)
+#endif
+
/* -----------------------------------------------------------------------------
For any registers which are denoted "caller-saves" by the C calling
convention, we have to emit code to save and restore them across C
@@ -456,6 +487,9 @@ GLOBAL_REG_DECL(P_,HpLim,REG_HpLim)
#endif
#ifdef CALLER_SAVES_Base
+#ifdef SMP
+#error "Can't have caller-saved BaseReg with SMP"
+#endif
#define CALLER_SAVE_Base /* nothing */
#define CALLER_RESTORE_Base BaseReg = &MainRegTable;
#else
@@ -463,10 +497,30 @@ GLOBAL_REG_DECL(P_,HpLim,REG_HpLim)
#define CALLER_RESTORE_Base /* nothing */
#endif
+#ifdef CALLER_SAVES_CurrentTSO
+#define CALLER_SAVE_CurrentTSO SAVE_CurrentTSO = CurrentTSO;
+#define CALLER_RESTORE_CurrentTSO CurrentTSO = SAVE_CurrentTSO;
+#else
+#define CALLER_SAVE_CurrentTSO /* nothing */
+#define CALLER_RESTORE_CurrentTSO /* nothing */
+#endif
+
+#ifdef CALLER_SAVES_CurrentNursery
+#define CALLER_SAVE_CurrentNursery SAVE_CurrentNursery = CurrentNursery;
+#define CALLER_RESTORE_CurrentNursery CurrentNursery = SAVE_CurrentNursery;
+#else
+#define CALLER_SAVE_CurrentNursery /* nothing */
+#define CALLER_RESTORE_CurrentNursery /* nothing */
+#endif
+
+#endif /* IN_STG_CODE */
+
/* ----------------------------------------------------------------------------
Handy bunches of saves/restores
------------------------------------------------------------------------ */
+#ifdef IN_STG_CODE
+
#define CALLER_SAVE_USER \
CALLER_SAVE_R1 \
CALLER_SAVE_R2 \
@@ -489,7 +543,9 @@ GLOBAL_REG_DECL(P_,HpLim,REG_HpLim)
CALLER_SAVE_Su \
CALLER_SAVE_SpLim \
CALLER_SAVE_Hp \
- CALLER_SAVE_HpLim
+ CALLER_SAVE_HpLim \
+ CALLER_SAVE_CurrentTSO \
+ CALLER_SAVE_CurrentNursery
#define CALLER_RESTORE_USER \
CALLER_RESTORE_R1 \
@@ -514,7 +570,18 @@ GLOBAL_REG_DECL(P_,HpLim,REG_HpLim)
CALLER_RESTORE_Su \
CALLER_RESTORE_SpLim \
CALLER_RESTORE_Hp \
- CALLER_RESTORE_HpLim
+ CALLER_RESTORE_HpLim \
+ CALLER_RESTORE_CurrentTSO \
+ CALLER_RESTORE_CurrentNursery
+
+#else /* not IN_STG_CODE */
+
+#define CALLER_SAVE_USER /* nothing */
+#define CALLER_SAVE_SYSTEM /* nothing */
+#define CALLER_RESTORE_USER /* nothing */
+#define CALLER_RESTORE_SYSTEM /* nothing */
+
+#endif /* IN_STG_CODE */
#define CALLER_SAVE_ALL \
CALLER_SAVE_SYSTEM \
diff --git a/ghc/includes/Rts.h b/ghc/includes/Rts.h
index 1dc23dd374..dd233886e0 100644
--- a/ghc/includes/Rts.h
+++ b/ghc/includes/Rts.h
@@ -1,5 +1,5 @@
/* -----------------------------------------------------------------------------
- * $Id: Rts.h,v 1.7 1999/08/25 16:11:44 simonmar Exp $
+ * $Id: Rts.h,v 1.8 1999/11/02 15:05:52 simonmar Exp $
*
* (c) The GHC Team, 1998-1999
*
@@ -10,8 +10,8 @@
#ifndef RTS_H
#define RTS_H
-#ifndef NO_REGS
-#define NO_REGS /* don't define fixed registers */
+#ifndef IN_STG_CODE
+#define NOT_IN_STG_CODE
#endif
#include "Stg.h"
diff --git a/ghc/includes/RtsAPI.h b/ghc/includes/RtsAPI.h
index 0e7883d8ef..aeccc7c3fd 100644
--- a/ghc/includes/RtsAPI.h
+++ b/ghc/includes/RtsAPI.h
@@ -1,5 +1,5 @@
/* ----------------------------------------------------------------------------
- * $Id: RtsAPI.h,v 1.7 1999/07/06 09:42:39 sof Exp $
+ * $Id: RtsAPI.h,v 1.8 1999/11/02 15:05:52 simonmar Exp $
*
* (c) The GHC Team, 1998-1999
*
@@ -14,6 +14,7 @@
* Running the scheduler
*/
typedef enum {
+ NoStatus, /* not finished yet */
Success,
Killed, /* another thread killed us */
Interrupted, /* stopped in response to a call to interruptStgRts */
diff --git a/ghc/includes/SMP.h b/ghc/includes/SMP.h
new file mode 100644
index 0000000000..fa247988cf
--- /dev/null
+++ b/ghc/includes/SMP.h
@@ -0,0 +1,91 @@
+/* ----------------------------------------------------------------------------
+ * $Id: SMP.h,v 1.1 1999/11/02 15:05:52 simonmar Exp $
+ *
+ * (c) The GHC Team, 1999
+ *
+ * Macros for SMP support
+ *
+ * -------------------------------------------------------------------------- */
+
+#ifndef SMP_H
+#define SMP_H
+
+/* SMP is currently not compatible with the following options:
+ *
+ * INTERPRETER
+ * PROFILING
+ * TICKY_TICKY
+ * and unregisterised builds.
+ */
+
+#if defined(SMP)
+
+#if defined(INTERPRETER) \
+ || defined(PROFILING) \
+ || defined(TICKY_TICKY)
+#error Build options incompatible with SMP.
+#endif
+
+/*
+ * CMPXCHG - this instruction is the standard "test & set". We use it
+ * for locking closures in the thunk and blackhole entry code. If the
+ * closure is already locked, or has an unexpected info pointer
+ * (because another thread is altering it in parallel), we just jump
+ * to the new entry point.
+ */
+#if defined(i386_TARGET_ARCH) && defined(TABLES_NEXT_TO_CODE)
+#define CMPXCHG(p, cmp, new) \
+ __asm__ __volatile__ ( \
+ "lock ; cmpxchg %1, %0\n" \
+ "\tje 1f\n" \
+ "\tjmp *%%eax\n" \
+ "\t1:\n" \
+ : /* no outputs */ \
+ : "m" (p), "r" (new), "r" (cmp) \
+ )
+
+/*
+ * XCHG - the atomic exchange instruction. Used for locking closures
+ * during updates (see LOCK_CLOSURE below) and the MVar primops.
+ */
+#define XCHG(reg, obj) \
+ __asm__ __volatile__ ( \
+ "xchgl %1,%0" \
+ :"+r" (reg), "+m" (obj) \
+ : /* no input-only operands */ \
+ )
+
+#else
+#error SMP macros not defined for this architecture
+#endif
+
+/*
+ * LOCK_CLOSURE locks the specified closure, busy waiting for any
+ * existing locks to be cleared.
+ */
+#define LOCK_CLOSURE(c) \
+ ({ \
+ const StgInfoTable *__info; \
+ __info = &WHITEHOLE_info; \
+ do { \
+ XCHG(__info,((StgClosure *)(c))->header.info); \
+ } while (__info == &WHITEHOLE_info); \
+ __info; \
+ })
+
+#define LOCK_THUNK(__info) \
+ CMPXCHG(R1.cl->header.info, __info, &WHITEHOLE_info);
+
+#define ACQUIRE_LOCK(mutex) pthread_mutex_lock(mutex);
+#define RELEASE_LOCK(mutex) pthread_mutex_unlock(mutex);
+
+#else /* !SMP */
+
+#define LOCK_CLOSURE(c) /* nothing */
+#define LOCK_THUNK(__info) /* nothing */
+#define ACQUIRE_LOCK(mutex) /* nothing */
+#define RELEASE_LOCK(mutex) /* nothing */
+
+#endif /* SMP */
+
+#endif /* SMP_H */
diff --git a/ghc/includes/SchedAPI.h b/ghc/includes/SchedAPI.h
index b682dfd686..02c308d661 100644
--- a/ghc/includes/SchedAPI.h
+++ b/ghc/includes/SchedAPI.h
@@ -1,5 +1,5 @@
/* -----------------------------------------------------------------------------
- * $Id: SchedAPI.h,v 1.6 1999/07/06 09:42:39 sof Exp $
+ * $Id: SchedAPI.h,v 1.7 1999/11/02 15:05:52 simonmar Exp $
*
* (c) The GHC Team 1998
*
@@ -17,13 +17,14 @@
* not compiling rts/ bits. -- sof 7/99
*
*/
-SchedulerStatus schedule(StgTSO *main_thread, /*out*/StgClosure **ret);
+SchedulerStatus waitThread(StgTSO *main_thread, /*out*/StgClosure **ret);
/*
* Creating threads
*/
-StgTSO *createThread (nat stack_size);
+StgTSO *createThread(nat stack_size);
+void scheduleThread(StgTSO *tso);
static inline void pushClosure (StgTSO *tso, StgClosure *c) {
tso->sp--;
diff --git a/ghc/includes/Stg.h b/ghc/includes/Stg.h
index 9b2ab0d5c0..756e8fb51a 100644
--- a/ghc/includes/Stg.h
+++ b/ghc/includes/Stg.h
@@ -1,5 +1,5 @@
/* -----------------------------------------------------------------------------
- * $Id: Stg.h,v 1.17 1999/07/06 09:42:39 sof Exp $
+ * $Id: Stg.h,v 1.18 1999/11/02 15:05:52 simonmar Exp $
*
* (c) The GHC Team, 1998-1999
*
@@ -16,6 +16,17 @@
#define _POSIX_SOURCE
#endif
+/* If we include "Stg.h" directly, we're in STG code, and we therefore
+ * get all the global register variables, macros etc. that go along
+ * with that. If "Stg.h" is included via "Rts.h", we're assumed to
+ * be in vanilla C.
+ */
+#ifdef NOT_IN_STG_CODE
+#define NO_REGS /* don't define fixed registers */
+#else
+#define IN_STG_CODE
+#endif
+
/* Configuration */
#include "config.h"
#ifdef __HUGS__ /* vile hack till the GHC folks come on board */
@@ -33,13 +44,17 @@
* For now, do lazy and not eager.
*/
-#define LAZY_BLACKHOLING
-/* #define EAGER_BLACKHOLING */
-
-#ifdef TICKY_TICKY
-/* TICKY_TICKY needs EAGER_BLACKHOLING to verify no double-entries of single-entry thunks. */
-# undef LAZY_BLACKHOLING
-# define EAGER_BLACKHOLING
+/* TICKY_TICKY needs EAGER_BLACKHOLING to verify no double-entries of
+ * single-entry thunks.
+ *
+ * SMP needs EAGER_BLACKHOLING because it has to lock thunks
+ * synchronously, in case another thread is trying to evaluate the
+ * same thunk simultaneously.
+ */
+#if defined(SMP) || defined(TICKY_TICKY)
+# define EAGER_BLACKHOLING
+#else
+# define LAZY_BLACKHOLING
#endif
/* ToDo: Set this flag properly: COMPILER and INTERPRETER should not be mutually exclusive. */
@@ -96,8 +111,10 @@ void _stgAssert (char *, unsigned int);
#include "ClosureTypes.h"
#include "InfoTables.h"
#include "TSO.h"
+#include "Block.h"
/* STG/Optimised-C related stuff */
+#include "SMP.h"
#include "MachRegs.h"
#include "Regs.h"
#include "TailCalls.h"
@@ -121,6 +138,10 @@ void _stgAssert (char *, unsigned int);
#include <unistd.h>
#endif
+#ifdef SMP
+#include <pthread.h>
+#endif
+
/* GNU mp library */
#include "gmp.h"
diff --git a/ghc/includes/StgMacros.h b/ghc/includes/StgMacros.h
index 3dec7513b0..b14ab43a82 100644
--- a/ghc/includes/StgMacros.h
+++ b/ghc/includes/StgMacros.h
@@ -1,5 +1,5 @@
/* -----------------------------------------------------------------------------
- * $Id: StgMacros.h,v 1.13 1999/10/13 16:39:21 simonmar Exp $
+ * $Id: StgMacros.h,v 1.14 1999/11/02 15:05:52 simonmar Exp $
*
* (c) The GHC Team, 1998-1999
*
@@ -416,12 +416,23 @@ EDI_(stg_gen_chk_info);
#define SET_TAG(t) /* nothing */
#ifdef EAGER_BLACKHOLING
-# define UPD_BH_UPDATABLE(thunk) \
- TICK_UPD_BH_UPDATABLE(); \
- SET_INFO((StgClosure *)thunk,&BLACKHOLE_info)
-# define UPD_BH_SINGLE_ENTRY(thunk) \
- TICK_UPD_BH_SINGLE_ENTRY(); \
- SET_INFO((StgClosure *)thunk,&SE_BLACKHOLE_info)
+# ifdef SMP
+# define UPD_BH_UPDATABLE(info) \
+ TICK_UPD_BH_UPDATABLE(); \
+ LOCK_THUNK(info); \
+ SET_INFO(R1.cl,&BLACKHOLE_info)
+# define UPD_BH_SINGLE_ENTRY(info) \
+ TICK_UPD_BH_SINGLE_ENTRY(); \
+ LOCK_THUNK(info); \
+ SET_INFO(R1.cl,&BLACKHOLE_info)
+# else
+# define UPD_BH_UPDATABLE(info) \
+ TICK_UPD_BH_UPDATABLE(); \
+ SET_INFO(R1.cl,&BLACKHOLE_info)
+# define UPD_BH_SINGLE_ENTRY(info) \
+ TICK_UPD_BH_SINGLE_ENTRY(); \
+ SET_INFO(R1.cl,&SE_BLACKHOLE_info)
+# endif
#else /* !EAGER_BLACKHOLING */
# define UPD_BH_UPDATABLE(thunk) /* nothing */
# define UPD_BH_SINGLE_ENTRY(thunk) /* nothing */
@@ -642,10 +653,15 @@ extern DLL_IMPORT_DATA const StgPolyInfoTable seq_frame_info;
We save all the STG registers (that is, the ones that are mapped to
machine registers) in their places in the TSO.
- The stack registers go into the current stack object, and the heap
- registers are saved in global locations.
+ The stack registers go into the current stack object, and the
+ current nursery is updated from the heap pointer.
+
+ These functions assume that BaseReg is loaded appropriately (if
+ we have one).
-------------------------------------------------------------------------- */
+#ifndef NO_REGS
+
static __inline__ void
SaveThreadState(void)
{
@@ -656,6 +672,12 @@ SaveThreadState(void)
CurrentTSO->splim = SpLim;
CloseNursery(Hp);
+#ifdef REG_CurrentTSO
+ SAVE_CurrentTSO = CurrentTSO;
+#endif
+#ifdef REG_CurrentNursery
+ SAVE_CurrentNursery = CurrentNursery;
+#endif
#if defined(PROFILING)
CurrentTSO->prof.CCCS = CCCS;
#endif
@@ -664,19 +686,30 @@ SaveThreadState(void)
static __inline__ void
LoadThreadState (void)
{
-#ifdef REG_Base
- BaseReg = (StgRegTable*)&MainRegTable;
-#endif
-
Sp = CurrentTSO->sp;
Su = CurrentTSO->su;
SpLim = CurrentTSO->splim;
OpenNursery(Hp,HpLim);
+#ifdef REG_CurrentTSO
+ CurrentTSO = SAVE_CurrentTSO;
+#endif
+#ifdef REG_CurrentNursery
+ CurrentNursery = SAVE_CurrentNursery;
+#endif
# if defined(PROFILING)
CCCS = CurrentTSO->prof.CCCS;
# endif
}
+/*
+ * Suspending/resuming threads for doing external C-calls (_ccall_GC).
+ * These functions are defined in rts/Schedule.c.
+ */
+StgInt suspendThread ( StgRegTable *cap );
+StgRegTable * resumeThread ( StgInt );
+
+#endif /* NO_REGS */
+
#endif /* STGMACROS_H */
diff --git a/ghc/includes/StgMiscClosures.h b/ghc/includes/StgMiscClosures.h
index c1ac9f078e..d9c3489fd1 100644
--- a/ghc/includes/StgMiscClosures.h
+++ b/ghc/includes/StgMiscClosures.h
@@ -1,5 +1,5 @@
/* -----------------------------------------------------------------------------
- * $Id: StgMiscClosures.h,v 1.14 1999/07/06 16:17:40 sewardj Exp $
+ * $Id: StgMiscClosures.h,v 1.15 1999/11/02 15:05:53 simonmar Exp $
*
* (c) The GHC Team, 1998-1999
*
@@ -24,6 +24,9 @@ STGFUN(CAF_ENTERED_entry);
STGFUN(CAF_BLACKHOLE_entry);
STGFUN(BLACKHOLE_entry);
STGFUN(BLACKHOLE_BQ_entry);
+#ifdef SMP
+STGFUN(WHITEHOLE_entry);
+#endif
#ifdef TICKY_TICKY
STGFUN(SE_BLACKHOLE_entry);
STGFUN(SE_CAF_BLACKHOLE_entry);
@@ -59,6 +62,9 @@ extern DLL_IMPORT_RTS const StgInfoTable CAF_ENTERED_info;
extern DLL_IMPORT_RTS const StgInfoTable CAF_BLACKHOLE_info;
extern DLL_IMPORT_RTS const StgInfoTable BLACKHOLE_info;
extern DLL_IMPORT_RTS const StgInfoTable BLACKHOLE_BQ_info;
+#ifdef SMP
+extern DLL_IMPORT_RTS const StgInfoTable WHITEHOLE_info;
+#endif
#ifdef TICKY_TICKY
extern DLL_IMPORT_RTS const StgInfoTable SE_BLACKHOLE_info;
extern DLL_IMPORT_RTS const StgInfoTable SE_CAF_BLACKHOLE_info;
diff --git a/ghc/includes/StgStorage.h b/ghc/includes/StgStorage.h
index 6b1237e384..6c9b0d3503 100644
--- a/ghc/includes/StgStorage.h
+++ b/ghc/includes/StgStorage.h
@@ -1,5 +1,5 @@
/* -----------------------------------------------------------------------------
- * $Id: StgStorage.h,v 1.4 1999/03/02 19:44:21 sof Exp $
+ * $Id: StgStorage.h,v 1.5 1999/11/02 15:05:53 simonmar Exp $
*
* (c) The GHC Team, 1998-1999
*
@@ -10,10 +10,6 @@
#ifndef STGSTORAGE_H
#define STGSTORAGE_H
-#include "Block.h"
-
-extern DLL_IMPORT_RTS bdescr *current_nursery;
-
/* -----------------------------------------------------------------------------
Allocation area for compiled code
@@ -29,10 +25,10 @@ extern DLL_IMPORT_RTS bdescr *current_nursery;
-------------------------------------------------------------------------- */
#define OpenNursery(hp,hplim) \
- (hp = current_nursery->free-1, \
- hplim = current_nursery->start + BLOCK_SIZE_W - 1)
+ (hp = CurrentNursery->free-1, \
+ hplim = CurrentNursery->start + BLOCK_SIZE_W - 1)
-#define CloseNursery(hp) (current_nursery->free = (P_)(hp)+1)
+#define CloseNursery(hp) (CurrentNursery->free = (P_)(hp)+1)
/* -----------------------------------------------------------------------------
Trigger a GC from Haskell land.
diff --git a/ghc/includes/Updates.h b/ghc/includes/Updates.h
index e33b4b3d28..cf8eabce17 100644
--- a/ghc/includes/Updates.h
+++ b/ghc/includes/Updates.h
@@ -1,5 +1,5 @@
/* -----------------------------------------------------------------------------
- * $Id: Updates.h,v 1.13 1999/10/20 10:14:47 simonmar Exp $
+ * $Id: Updates.h,v 1.14 1999/11/02 15:05:53 simonmar Exp $
*
* (c) The GHC Team, 1998-1999
*
@@ -35,10 +35,25 @@
/* UPD_IND actually does a PERM_IND if TICKY_TICKY is on;
if you *really* need an IND use UPD_REAL_IND
*/
-#define UPD_REAL_IND(updclosure, heapptr) \
- AWAKEN_BQ(updclosure); \
+#ifdef SMP
+#define UPD_REAL_IND(updclosure, heapptr) \
+ { \
+ const StgInfoTable *info; \
+ info = LOCK_CLOSURE(updclosure); \
+ \
+ if (info == &BLACKHOLE_BQ_info) { \
+ STGCALL1(awakenBlockedQueue, \
+ ((StgBlockingQueue *)updclosure)->blocking_queue); \
+ } \
updateWithIndirection((StgClosure *)updclosure, \
+ (StgClosure *)heapptr); \
+ }
+#else
+#define UPD_REAL_IND(updclosure, heapptr) \
+ AWAKEN_BQ(updclosure); \
+ updateWithIndirection((StgClosure *)updclosure, \
(StgClosure *)heapptr);
+#endif
#if defined(PROFILING) || defined(TICKY_TICKY)
#define UPD_PERM_IND(updclosure, heapptr) \
@@ -110,11 +125,12 @@ extern DLL_IMPORT_DATA const StgPolyInfoTable Upd_frame_info;
extern void newCAF(StgClosure*);
-#define UPD_CAF(cafptr, bhptr) \
- { \
- SET_INFO((StgInd *)cafptr,(const StgInfoTable*)&IND_STATIC_info); \
- ((StgInd *)cafptr)->indirectee = (StgClosure *)(bhptr); \
- STGCALL1(newCAF,(StgClosure *)cafptr); \
+#define UPD_CAF(cafptr, bhptr) \
+ { \
+ LOCK_CLOSURE(cafptr); \
+ ((StgInd *)cafptr)->indirectee = (StgClosure *)(bhptr); \
+ SET_INFO((StgInd *)cafptr,(const StgInfoTable*)&IND_STATIC_info); \
+ STGCALL1(newCAF,(StgClosure *)cafptr); \
}
/* -----------------------------------------------------------------------------