:TITLE[MesaP];
%
Ed Fiala 25 August 1982: Absorbed RequeueSub in its two callers and ExitM2
  in its two callers to speed up MX and MW opcodes, while changing prFault
  slightly; fixed bug in MW not interlocking prPsbIndex; renamed
  RequeueSubPsbFetched to be RequeueSub, ExitM1 to be StoreMonitor;
  eliminated PStore4 after return at RequeueExit as a precaution; moved Fetch
  of ReadyQ↑ to RequeueExit; altogether bummed 5 mi.
Ed Fiala 21 May 1982: PushSD for NoPushSD; replace prPsbLink.next by
  prNextPsbLink; bum 2 mi at prFault; convert 2 mi at RSLoadAndFreeState to
  1 mi on prPage.
Ed Fiala 14 May 1982: Reduced tasking time for @SPP, @ME, RequeueExit,
  @MW, UpdateConditionQueue, Interrupt, RSSaveProcess, CheckForTimeoutLoop;
  introduce LinkOrT subr; remove PStore1[prMonitorQ...] at MonitorFetch+1
  and add it at EntryFailed (should be safe against write protect fault;
  improves tasking and speed).  Fixed bug in @MW not refetching current Psb
  after ExitM2 call.  Speeded WakeHead, CleanUpQueue.  Removed PFetch4 at
  opcode dispatch and added it at jumps to EntryFailed and in @MR opcode
  speeding up the process opcodes by 4 cycles each; introduced prIntSaveStkP
  and prIntPdaTimeout registers in CheckForTimeout code; speeded up
  CheckForTimeoutLoop substantially.
Ed Fiala 15 March 1982: bum 1 mi in MXDepart by shuffling ProcessDisp
  offsets, 1 mi in SPPOp; 2 mi in CleanUpQueue.  Eliminated SPPloc because
  there is no room for it in the current dispatch and jump directly to SPPOp
  without minimal stack error check; undid 1 mi bug in Reschedule; speed up
  code at Interrupt a little; replace prPdaTimeout at CheckForTimeouts by
  prCurrentSAT.
Jim Sandman 8 Mar 1982: Implemented SPP.  reordered dispatch to include
  SPP.  added 6 mi.
Ed Fiala 5 March 1982: advanced the call to SavPCinFrame in
  RSSaveProcess; changed T to (Zero) or T there; eliminated RSAllocState,
  RSSVError, RSSVAvailable, and RSSaveStack labels; put in shell for new
  @SPP opcode; fix bug in @MX.
Ed Fiala 11 December 1981: Converted process opcodes to long mode only
  for new instruction set; changed them to Esc opcodes on xfPage1; bummed
  12 mi elsewhere in code; remove Bravo paragraphing and reabsorb MesaPDefs;
  replaced ExitMon subroutine by ExitM1 and ExitM2; absorbed NotifyWakeup
  subr in its two callers using NWUXXX now (eliminates prRtnLink2, saving
  1 RM register).
Jim Sandman 4 December 1981: Put in code to get timeouts from separate
  timeout vector and get mds field from psb.  Added 3 mi in MXWait, 3 mi in
  WakeHead, and 7 mi in CheckForTimeouts to do timeout vector change, and 5 mi
  in RSXfer to do mds field.
Ed Fiala 22 September 1981: P4Ret edits; Idle loop change; minimal
  stack error check bugfix; bum 3 mi.
Original version by Jim Sandman; major changes by Jim Frandeen; other edits
  by Rich Johnsson and Ev Neely.
%

*Psb (Process State Block--Kathy Calls it Pacific States Baloney) format.
MC[psbLink,0];		*Word 0: PsbLink (defined below).
MC[psbFlags,1];		*Word 1: PsbFlags (defined below).
MC[psbContext,2];	*Word 2: Pointer to State Vector or pointer to frame.
MC[psbMds,3];		*Word 3: MDS of process
MC[PsbSize,4];

*PsbLink format.
MC[enterFailed,100000];	*Bit 0: = 1 if entry to monitor failed. This means
			*the Psb is on a Monitor queue.
MC[priority,70000];	*Bits 1..3: priority of Psb
Set[priBitPos,1];	*Bit position of priority field for LdF inst..
Set[priFldSize,3];	*Size of priority field for LdF inst..
Set[next,7774];		*Bits 4..15B: PsbIndex of next Psb in the queue.
MC[linkReserved,2];	*Bit 16B: Currently not used.
MC[vector,1];		*Bit 17B: = 1 if if psbContext points to a StateVector.

*PsbFlags format.
MC[softwareState,140000];	*Bits 0..1: used only by software.
MC[flagsReserved,34000];	*Bits 2..3: Currently not used.
Set[cleanup,7774];	*Bits 4..15B: PsbIndex of cleanup link.
MC[waiting,2];		*Bit 16B: = 1 if process waiting on a
			*condition queue.
MC[abortPending,1];	*Bit 17B: = 1 if process will be aborted at next wait.

*Condition format. A process is moved to a condition variable queue when it
*executes a WAIT statement.
MC[conditionReserved,170000];	*Currently not used, = zero.
Set[conditionTail,7774];	*Bits 4..15B: PsbIndex of tail of condition queue.
MC[abortable,2];	*Bit 16B: = 1 if abortable.
MC[wakeup,1];		*Bit 17B: This is set by NakedNotify if queue empty.

*Monitor format. A process is moved to a montior lock queue when it has
*failed to enter a monitor because some other process is already inside the
*monitor.
MC[monitorReserved,170000];	*Currently not used, = zero.
Set[monitorTail,7774];	*Bits 4..15B: PsbIndex of tail of monitor queue.
MC[monitorLock,1];	*Bit 17B: = 1 if monitor is locked, = 0 if monitor is unlocked.

*State Vector format.
MC[svNext,0];		*Word 0 is a pointer to the next StateVector (0 if
			*none) when StateVectors are not being used.
MC[svStack,0];		*Word 0..15: contents of stack.
MC[svStack4,4];		*Word 4 of stack.
MC[svStack8,10];	*Word 8 of stack.
MC[svStack12,14];	*Word 12 of stack.
MC[svWord,16];		*Word 16B: StateWord [break : BYTE,  stkptr : Byte].
MC[svFrame,17];		*Word 17B: used to save Local.
MC[svData,20];		*Word 20B..21B: Unspecified.

%Registers preserved across opcodes:

CurrentPsb	Contains PsbIndex of the current Psb. This points to the front
		of the ready queue.
Pda,PdaHi	This base register pair points to the Pda. The Pda is assigned
		to location 200000. The register pair RZero and R400 are used
		to point to the Pda. 400 in the high byte works because the
		Pda will not cross a page boundary.
PsbIndexMask	This contains a mask for the PsbIndex
Ticks		Current tick count for timeout clock.
Time		This gets decremented by one at each scan line 0. When this
		gets to zero, we set it back to TickSize (3) and add one to
		Ticks.

Registers preserved across Process operations:

Condition	Contains ConditionQ↑.
ConditionQ,Hi	Base register pair points to a condition queue.
Flags		Holds Opcode dispatch values and flags (described below)

bit 0		0 =>	Notify
		1 =>	Broadcast
bits 1-2  Source Queue:	0 =>	Ready Queue
			1 =>	Monitor Queue
			2 =>	Condition Queue
bits 3-4  Destination Queue:
			0 =>	Ready Queue
			1 =>	Monitor Queue
			2 =>	Condition Queue
bits 5-10 Opcode Disp:	0 =>	Monitor Entry
			2 =>	Monitor ReEntry
			4 =>	Monitor Wait
			10 =>	Monitor Depart
			14 =>	Notify and Broadcast
			16 =>	Requeue
bit 11		0 =>	Requeue not done
		1 =>	Requeue done
bits 12-15	Unused
bit 16		1 =>	Reschedule called from Interrupt; save stack
		0 =>	Don't save stack.
bits 17		1 =>	Source queue not nil
		0 =>	Source Queue nil

Monitor		Contains MonitorQ↑
MonitorQ,Hi	This base register pair is used to point to a monitor queue.
Timeout		Used by MXWait to save timeout parameter.

Temporary registers shared between Requeue, CleanUpCondition, and Reschedule.
The first four are a quadword so a Psb can be fetched and stored at once:

PsbLink		Contains PsbLink.
PsbFlags	Contains PsbFlags
PsbState	Contains PsbState (frame pointer)
PsbMds		MDS field of Psb
ConditionTail	Used by CleanUpCondition.
StackPointer	Used by Reschedule to save and restore the stack pointer.
Frame		Used by Reschedule to save LOCAL in the State Vector.
NextPsb		Used by RequeueSub to enqueue a Psb.
PsbIndex	Points to PsbLink.
PrevPsbIndex	Used by requeue subroutine to point to PrevPsbLink.
PrevPsbLink	Used by requeue subroutine to chain and unchain Psbs.
PsbPriority	Used by RequeueSub to contain priority of Psb to be requeued.
NextPsbLink	Used by RequeueSub to save PsbLink.next.
Queue		Used by Requeue to contain SourceQueue↑ and DestQueue↑.
QueueTail	Used by CleanUpCondition to save ConditionQueue.tail.
QTemp,Hi	Used by RequeueSub to point to SourceQ and DestQ; used by
		Reschedule for LoadState and SaveState.
ReturnLink	Used by all subroutines save return.
State,Hi	Base reg pair used by Reschedule to point to a State Vector.
PdaTimeout	Used by MXWait, WakeHead, and TimeoutScan to hold pointer to
		Timeout vector.
%

*DISPATCH TABLES:
Loca[ProcessDisp,prPage,0];
Loca[QueueDisp,prPage,20];

*Flag values:
Set[ReadyQbits,0];
Set[MonitorQbits,1];
Set[ConditionQbits,2];
Set[SourceQbit,1];
Set[DestQbit,3];
Set[SourceIsReadyQ,LShift[ReadyQbits,15]];
Set[SourceIsMonitorQ,LShift[MonitorQbits,15]];
Set[SourceIsConditionQ,LShift[ConditionQbits,15]];
Set[DestIsReadyQ,LShift[ReadyQbits,13]];
Set[DestIsMonitorQ,LShift[MonitorQbits,13]];
Set[DestIsConditionQ,LShift[ConditionQbits,13]];
Set[ReadyQtoReadyQ,Or[SourceIsReadyQ,DestIsReadyQ]];
Set[ReadyQtoMonitorQ,Or[SourceIsReadyQ,DestIsMonitorQ]];
Set[MonitorQtoReadyQ,Or[SourceIsMonitorQ,DestIsReadyQ]];
Set[ReadyQtoConditionQ,Or[SourceIsReadyQ,DestIsConditionQ]];
Set[ConditionQtoReadyQ,Or[SourceIsConditionQ,DestIsReadyQ]];
Set[MonitorQtoConditionQ,Or[SourceIsMonitorQ,DestIsConditionQ]];

*The following locations must be at even numbers. The last bit is truncated
*in the Flags constant, and the Dispatch picks up 4 bits with a zero in the
*last bit.
Set[MEloc,0];
Set[MREloc,2];
Set[MXWloc,4];	*MXWloc to MXWloc+3 used
Set[MXDloc,10];	*MXDloc to MXDloc+2 used
Set[NotifyBroadcastLoc,14];	*NotifyBroadcastLoc+1 also used
Set[REQloc,16];
Set[BroadcastBit,100000];
Set[SaveStackBit,2];
*Dispatch bits in bits 5-10
MC[MEFlags,Add[LShift[MEloc,7],ReadyQtoMonitorQ]];
MC[MREFlags,Add[LShift[MREloc,7],ReadyQtoMonitorQ]];
MC[MXWFlags,Add[LShift[MXWloc,7],MonitorQtoReadyQ]];
MC[MXDFlags,Add[LShift[MXDloc,7],MonitorQtoReadyQ]];
MC[NOTIFYFlags,Add[LShift[NotifyBroadcastLoc,7],ConditionQtoReadyQ]];
MC[BCASTFlags,Add[LShift[NotifyBroadcastLoc,7],
  ConditionQtoReadyQ,BroadcastBit]];
MC[SPPFlags,ReadyQtoReadyQ];
MC[REQFlags,Add[LShift[REQloc,7],MonitorQtoConditionQ]];
MC[FaultFlags,ReadyQtoConditionQ];
MC[RequeueOccurred,100];
MC[TimeoutFlags,ConditionQtoReadyQ];
MC[RequeueReadyQtoConditionQ,ReadyQtoConditionQ];
MC[InterruptFlags,ConditionQtoReadyQ];
MC[SourceQNil,1];
MC[SaveStack,SaveStackBit];

*Monitor Entry. Stack contains long pointer to Monitor.
*Timing: ~14.5+28+WriteTail = ~62.5 cycles in the ordinary case.
@ME:	prFlags ← MEFlags, GoToP[MonitorDsp], At[EscD0,0];

*Monitor Exit. Stack contains long pointer to Monitor.
*Timing: ~14.5+58 = ~72.5 cycles in the ordinary case.
@MX:	prFlags ← MXDFlags, GoToP[MonitorDsp], At[EscD0,1];

*Monitor Wait. Stack contains time, long pointer to Condition, and long pointer to Monitor.
@MW:	prFlags ← MXWFlags, GoToP[.+1], At[EscD0,2];
OnPage[xfPage1];
	T ← Stack&-1;
	prData ← T, GoTo[MonAndCondDsp];

*Monitor Reentry. Stack contains long pointer to Condition and long pointer to Monitor.
@MR:	prFlags ← MREFlags, GoToP[MonAndCondDsp], At[EscD0,3];

*Notify Condition. Stack contains long pointer to Condition.
@NC:	prFlags ← NOTIFYFlags, GoToP[ConditionDsp], At[EscD0,4];

*Broadcast Condition. Stack contains long pointer to Condition.
@BC:	prFlags ← BCASTFlags, GoToP[ConditionDsp], At[EscD0,5];

*Set Process Priority. Put priority in TOS into current PSB and requeue
*from ready list to ready list.
@SPP:	T ← prCurrentPsb, LoadPage[prPage], GoToP[.+1], At[EscD0,17];
OnPage[xfPage1];
	PFetch4[prPda,prPsbLink], GoToP[.+1];
%Clear priority field and enterFailed bit; clearing enterFailed is harmless
because it is known to be 0.
***Didn't do minimal stack error check here.
%
OnPage[prPage];
	prFlags ← SPPFlags, Task;
	prPsbIndex ← T;
	T ← LSh[Stack&-1,14];
	prPsbLink ← (LdF[prPsbLink,4,14]) or T, GoTo[Requeue&Reschedule];

*Requeue. Stack contains a Psb index, a long pointer to a source queue,
*and a long pointer to a destination queue. Put the source queue in
*MonitorQueue, destination queue in ConditionQueue.
@REQ:	T ← Stack&-1, GoToP[.+1], At[EscD0,6];
OnPage[xfPage1];
	prPsbIndex ← T;
:IF[LPChecking]; ************************************
	LU ← LdF[Stack,0,12], Call[FixConditionQueue];
*Trigger write protect fault if protected.
	PStore1[prConditionQ,prCondition,0];
	LU ← LdF[Stack,0,12], Call[FixMonitor];
:ELSE; **********************************************
	T ← LSh[Stack&-1,10], Call[FixConditionQueue];
*Trigger write protect fault if protected.
	PStore1[prConditionQ,prCondition,0];
	T ← LSh[Stack&-1,10], Call[FixMonitor];
:ENDIF; *********************************************
	LU ← (prMonitorQhi) or T;	*Check for nil long pointer.
	prFlags ← REQFlags, Skip[ALU#0];
*Only on RequeueOp, check for nil source and don't fetch Monitor.
*Other opcodes allow address fault.
	  prFlags ← (prFlags) or (SourceQNil), GoTo[ProcessOps];
	GoTo[MonitorFetch];

:IF[LPChecking]; ************************************
MonAndCondDsp:
	LU ← LdF[Stack,0,12], Call[FixConditionQueue];
*Trigger write protect fault if protected.
	PStore1[prConditionQ,prCondition,0];
MonitorDsp:
	LU ← LdF[Stack,0,12], Call[FixMonitor];
:ELSE; **********************************************
MonAndCondDsp:
	T ← LSh[Stack&-1,10], Call[FixConditionQueue];
*Trigger write protect fault if protected.
	PStore1[prConditionQ,prCondition,0];
MonitorDsp:
	T ← LSh[Stack&-1,10], Call[FixMonitor];
:ENDIF; *********************************************
MonitorFetch:
	PFetch1[prMonitorQ,prMonitor,0], Call[xfRet];
*Note that these opcodes must be minimal stack because the
*stack is not saved while other processes are running.
ProcessOps:
	T ← (SStkP&NStkP) + 1, LoadPage[prPage];
	Dispatch[prFlags,5,4], GoToP[.+3,H2Bit8'];
OnPage[prPage];
	  LoadPageExternal[FaultPage];
	  GoToExternal[StackErrorLoc];
	T ← prCurrentPsb, Disp[ME1];

OnPage[xfPage1];

*All we use ConditionQ for is to fetch and store one word, so we don't need
*to create a perfect base register.
:IF[LPChecking]; ************************************
ConditionDsp:
	LU ← LdF[Stack,0,12], Call[FixConditionQueue];
*Trigger write protect fault if protected
	PStore1[prConditionQ,prCondition,0], GoTo[ProcessOps];

FixConditionQueue:
	T ← LSh[Stack&-1,10], Skip[ALU=0];	*Long pointer
	  T ← (Zero) - 1;			*Cause map out of bounds.
	prConditionQhi ← T;
:ELSE; **********************************************
ConditionDsp:
	T ← LSh[Stack&-1,10], Call[FixConditionQueue];
*Trigger write protect fault if protected
	PStore1[prConditionQ,prCondition,0], GoTo[ProcessOps];

FixConditionQueue:
	prConditionQhi ← T;
:ENDIF; *********************************************
	T ← Stack&-1;
	prConditionQ ← T;
	PFetch1[prConditionQ,prCondition,0], GoTo[xfRet];

*All we use MonitorQ for is to fetch and store one word, so we don't need to
*create a perfect base register.
:IF[LPChecking]; ************************************
FixMonitor:
	T ← LSh[Stack&-1,10], Skip[ALU=0];	*Long pointer
	  prMonitorQhi ← (Zero) - 1, Skip;	*Cause map out of bounds.
	prMonitorQhi ← T;
:ELSE; **********************************************
FixMonitor:
	prMonitorQhi ← T;
:ENDIF; *********************************************
	T ← Stack&-1;
	prMonitorQ ← T, Return;

	PFetch4[PCB,IBuf,4], GoToP[MesaRefill], At[LShift[prPage,10],377];

%Monitor Entry is executed by an entry procedure of a Mesa monitor. It returns
TRUE on the stack if the monitor was not locked; otherwise the running process
is put on the monitor queue, and the stack is left empty.

Input:	MonitorQ	base register pair points to Monitor
	Monitor		contains MonitorQ↑
	T		points at CurrentPsb
Exits:	prTail		if enter successful
	EntryFailed	if enter unsuccessful
%
*IF Monitor.locked THEN GoTo EntryFailed; Monitor.lock ← locked
ME1:	prMonitor ← (prMonitor) or (monitorLock), Skip[R Even], At[ProcessDisp,MEloc];
	  PFetch4[prPda,prPsbLink], GoTo[EntryFailed];
*No need to Call Reschedule because no requeue has occurred.
	PStore1[prMonitorQ,prMonitor,0];	*Store Monitor
LockMonitor&Exit:
	Call[Nop2];	*Allow write-protect fault before smashing stack
	Stack&+1 ← 1C;	*Push[TRUE].
prTail:
	LU ← NextInst[IBuf];
prTailx:
	NIRet;

Nop2:	GoTo[TGetsPsbIndexMask];

%Come here if monitor is already locked with EnterFailed set in prPsbLink and
prCurrentPsb in T.  Move the current process from ready queue to monitor lock
queue.  PsbLink will be updated by Requeue when the Psb is stored at exit.
Store monitor to trigger write protect fault before anything irreversible is
done.
%
EntryFailed:
	prPsbIndex ← T, Call[StoreMonitor];
	prPsbLink ← (prPsbLink) or (EnterFailed), GoTo[Requeue&Reschedule];


%Monitor Re-Entry is used to re-enter a monitor which a process has exited
in order to wait on a condition variable queue. If the monitor is locked, the
process is placed on the monitor lock queue as in the ME instruction.

Input:	MonitorQ	base register pair points to Monitor
	Monitor		contains MonitorQ↑
	ConditionQ	base register pair points to Condition
	Condition	contains ConditionQ↑
	T		points at CurrentPsb
Subroutines called:
	CleanUpQueue	if enter successful
Exits:	EntryFailed	if enter unsuccessful, else
	PRTrap		if abortPending and abortable, else
	prTail		if enter successful
%
@MR1:	prMonitor ← (prMonitor) or (monitorLock), Skip[R Even], At[ProcessDisp,MREloc];
	  PFetch4[prPda,prPsbLink], GoTo[EntryFailed];
	PFetch4[prPda,prPsbLink];
	T ← prPsbIndexMask, Call[CleanUpQueue];	*Clean up the condition queue.
*Return with PsbIndexMask in T; zero Flags.CleanupLink.
	prPsbFlags ← (prPsbFlags) and not T, Call[StoreCurrentPsb];
*If ~flags.abortPending THEN {Push[TRUE];exit}. No need to Call Reschedule
*because no requeue has occurred.
	LU ← (prPsbFlags) and (AbortPending);
	LU ← (prCondition) and (abortable), Skip[ALU#0];
	  PStore1[prMonitorQ,prMonitor,0], GoTo[LockMonitor&Exit];
	RTemp ← sProcessTrap, GoTo[PRTrap,ALU#0];
	  PStore1[prMonitorQ,prMonitor,0], GoTo[LockMonitor&Exit];
*Trap if condition.abortable and PsbFlags.AbortPending.
PRTrap:	LoadPage[opPage0];
	T ← SStkP, GoToP[BackSPPCandTrap];

%Monitor Exit is executed at the end of a Mesa monitor entry procedure.
It unlocks the monitor and, if the monitor queue is non-empty, moves its
first (i.e., highest priority) entry to the ready queue. 

Input:	MonitorQ	base register pair points to Monitor
	Monitor		contains MonitorQ↑
	T		points at CurrentPsb
Exits:	REQ1
%
@MX1:	prMonitor ← (prMonitor) and not (monitorLock), Call[StoreMonitor], At[ProcessDisp,MXDloc];
	T ← (prMonitor) and T;
	Skip[ALU#0];
	  LU ← NextInst[IBuf], CallX[prTailx];
	PFetch1[prPda,prPsbIndex], GoTo[REQ1];

%Monitor Wait is executed within a monitor when it is desirable to wait on a
condition variable. It unlocks the monitor, and if the monitor queue is
non-empty, its first entry is moved to the ready queue. If there is not a
wakeup waiting or an abort pending, then the process executing the MW is moved
to the condition variable queue; otherwise it remains on the ready list.

Input:	MonitorQ	base register pair points to Monitor
	Monitor		contains MonitorQ↑
	ConditionQ	base register pair points to Condition
	Condition	contains ConditionQ↑
	prData		contains time out value
	T		points at CurrentPsb
Output:	PsbIndex	CurrentPsb for Requeue
	PsbLink		four-word buffer contains CurrentPsb
Subroutines called:
	CleanUpQueue
	RequeueSub
Exits:	Reschedule
%

@MW1:	T ← prPsbIndexMask, Call[CleanUpQueue], At[ProcessDisp,MXWloc];
	prMonitor ← (prMonitor) and not (monitorLock), Call[StoreMonitor];
	T ← (prMonitor) and T;
*Fetch monitor.tail and jump if NIL.
	GoTo[MW2,ALU=0];
	  PFetch1[prPda,prPsbIndex], Call[TGetsPsbIndexMask];
	  prPsbIndex ← T ← (prPsbIndex) and T;
	  PFetch4[prPda,prPsbLink], Call[RequeueSub0];
MW2:	T ← prCurrentPsb;
	prPsbIndex ← T, Call[FetchPsb];
*If PsbFlags.abortPending and Condition.abortable, then abort.
	LU ← (prCondition) and (abortable);
	LU ← (prPsbFlags) and (AbortPending), Skip[ALU#0];
	  PFetch1[prPda,prPdaTimeout,pdaTimeout!], GoTo[MXWait1];
	PFetch1[prPda,prPdaTimeout,pdaTimeout!], Skip[ALU=0];
	  LU ← (prFlags) and (RequeueOccurred), GoTo[RescheduleIfRequeueOccurred];
*Condition.wakeup ← FALSE.  If prior ~condition.wakeup, GoTo MonitorOntoCV
*ELSE store condition.
MXWait1:
	prCondition ← (prCondition) and not (wakeup), GoTo[MonitorOntoCV,R Even];
	PStore1[prConditionQ,prCondition,0], Call[prRet];
*Also get here from @NC opcode.
*Time to task below here can be as long as 22 cycles.
NotifyExit:
	LU ← (prFlags) and (RequeueOccurred), GoTo[RescheduleIfRequeueOccurred];

MonitorOntoCV:	*Put timeout in Psb (i.e., in timeout table).
	LU ← prData;
*Jump to zero the timeout.
	prSaveStkP ← IP[prTicks]C, GoTo[StoreTimeout,ALU=0];
*Use StkP to address prTicks (outside RM 0-77)
	T ← (SStkP&NStkP) xor (377C), Call[prStkPSwap];
	T ← Stack, Call[prStkPSwap];	*Restore StkP
*Timeout ← MAX[1,Ticks+Timeout]
	prData ← (prData) + T;
StoreTimeout:
	prFlags ← RHMask[prFlags], Skip[ALU#0];
	  prData ← 1C;
	T ← RSh[prCurrentPsb,2], Call[AddTimeout];
	PStore1[prPda,prData], Task;
*Save Requeue bit
*Set up prFlags so to requeue from ReadyQ to ConditionQ.
*Initially, we were set up to move from the MonitorQ to the ReadyQ.
	prFlags ← (prFlags) or (RequeueReadyQtoConditionQ);
*Psb.waiting ← TRUE.
	prPsbFlags ← (prPsbFlags) or (waiting), GoTo[Requeue&Reschedule];

prStkPSwap:
	prSaveStkP ← T, StkP ← prSaveStkP, NoRegILockOK, Return;

%Notify moves the 1st entry of a condition variable queue to the ready queue.
Broadcast moves all entries of a condition variable queue to the ready queue.

Input:	ConditionQ	base register pair points to Condition
	Condition	contains ConditionQ↑
	T		points at CurrentPsb
Exits:	Reschedule
%
@NC1:
@BC1:	T ← prPsbIndexMask, Call[CleanUpQueue], At[ProcessDisp,NotifyBroadcastLoc];
	T ← prCondition ← (prCondition) and T, GoTo[NotifyTestCondition];

NotifyLoop:
	PFetch1[prConditionQ,prCondition,0], Call[TGetsPsbIndexMask];
	T ← prCondition ← (prCondition) and T;
NotifyTestCondition:
	GoTo[NotifyExit,ALU=0];	*IF condition.tail = nil Then Exit
	UseCTask, Call[WakeHead];
*Loop IF broadcast
	LU ← (prFlags) and (RequeueOccurred),
		DblGoTo[NotifyLoop,RescheduleIfRequeueOccurred,R<0];


%Move the first Psb on ConditionQueue to the ready queue.  WakeHead is called
by @BC or @NC; on interrupt processing when an io controller has set a bit in
NWW corresponding to a condition in Pda.Interrupt; and on fault processing for
the fault condition queue.  The fault and interrupt calls are made through
the NWUXXX subroutine.

Input:	ConditionQ	base register pair points to Condition
	Condition	contains ConditionQ↑ not nil
Output:	PsbIndex	Condition.tail↑ for Requeue
	PsbLink		four-word buffer contains Psb pointed to by PsbIndex
Subroutines called:
	RequeueSub
Exits:	Return to caller from RequeueSub
Timing:	41 cycles to RequeueSub
%
WakeHead:	*Returns with PsbIndexMask in T.
	T ← APCTask&APC, Call[SaveReturnInReturnLink];
	T ← (prCondition) and T, Task;
*Fetch condition.tail↑ into PsbIndex for Requeue.
	PFetch1[prPda,prPsbIndex];
	PFetch1[prPda,prPdaTimeout,pdaTimeout!], Call[TGetsPsbIndexMask];
*Fetch PsbIndex↑ into 4-word Psb buffer.
	T ← prPsbIndex ← (prPsbIndex) and T, Call[FetchPsb];
*Zero timeout.
	T ← RSh[prPsbIndex,2], Call[AddTimeout];
	PStore1[prPda,RZero];
*Psb.waiting ← FALSE.
	prPsbFlags ← (prPsbFlags) and not (waiting), GoTo[RequeuePsbFetched];

%Requeue, given a PsbIndex two queue pointers, moves the process from the
source queue and inserts it according to priority into the destination queue.

Input:	ConditionQ	base register pair points to Dest queue (if needed)
	MonitorQ	base register pair points to Source queue (if needed)
	PsbIndex	points to Psb to be requeued

Exits:	Reschedule
%
REQ1:	T ← prPsbIndexMask, At[ProcessDisp,REQloc];
	T ← prPsbIndex ← (prPsbIndex) and T, Call[FetchPsb];
*Jump here from @SPP, StoreTimeout, and EntryFailed.
Requeue&Reschedule:
	UseCTask, Call[RequeueSub];
RescheduleCurrent:
	T ← prCurrentPsb, GoTo[Reschedule];


%Requeue is called:
	1. by EntryFailed to move a Psb from the ready to a monitor queue.
	2. by @MX and @MW to move a Psb from the monitor queue to the ready
	queue.
	3. by @MW to move a Psb from the ready queue to a condition queue.
	4. by WakeHead to move a Psb from a condition queue to the ready
	queue.  WakeHead may have been called by Interrupt.
	5. by TimeOut to move a Psb from an unknown condition queue (the
	source queue points to the first condition in the ConditionVector
	of the PDA) to the ready queue.
	6. by RequeueOp to move a Psb from the source queue (we use MonitorQ)
	to the dest queue (we use ConditionQ).
Input:	prFlags		indicates source and dest queues
	PsbIndex	PsbIndex of Psb to be requeued
Output:	prFlags		set to indicate requeue occurred
	Ready		Contains ReadyQueue↑
Temps:	PsbLink		4-word buffer contains PsbIndex↑
	NextPsbLink	Next link of PsbLink
	PrevPsbIndex	Points to previous Psb
	PrevPsbLink	PrevPsbIndex↑.
	PsbPriority	Priority of Psb to be requeued
	QTemp		Base register pair used to reference source and dest
			queues
	Queue		Contains QTemp↑
	NextPsb		Used by Enqueue to chain Psb according to priority
Exits:	Return to caller
%
Requeue1:
	prNextPsbLink ← T, Skip[ALU#0];
*THEN prev ← nil--we won't need to unchain Psb.
	  prPrevPsbIndex ← Zero, GoTo[SetCleanupLink];
*Continue if the Psb does not point to itself. We must remove it from the
*source queue. Search for the preceding Psb in the queue. When we are through,
*PrevPsbIndex will point to the Psb preceding the Psb we wish to dequeue, and,
*PrevPsbLink will contain the Link word of the preceding Psb. Start our search
*from the tail of the source queue if we know what queue we are on; otherwise
*search from the Psb being dequeued.
	A ← prFlags, Skip[R Even];	*Know SourceQNil=1
*IF source queue nil THEN PrevPsbIndex ← Link.next
	  prPrevPsbIndex ← T, GoTo[FetchPrev];
*Fetch SourceQ↑ into Queue.
	PFetch1[prQTemp,prQueue,0], GoTo[TGetsPsbIndexMask];

RequeueSub0:
	UseCTask;
RequeueSub:	*Returns with PsbIndexMask in T
	T ← APCTask&APC, Call[SaveReturnInReturnLink];
RequeuePsbFetched:	*Set QTemp to SourceQ. Returns with PsbIndexMask in T.
	Dispatch[prFlags,SourceQbit,2], Call[SetQTemp];
*First, traverse the source queue looking for the Psb immediately before the
*Psb pointed to by PsbIndex so that this Psb can be bypassed in the linked
*queue structure. This starts with the last Psb of a queue since the process
*instructions always remove the first Psb and the last entry always points to
*the first.
	T ← LdF[prPsbLink,1,3];	*Load PsbLink.priority
*Save priority of Psb to be requeued.
	prPsbPriority ← T, Call[TGetsPsbIndexMask];
*See if Psb to be requeued points to itself. If so, we won't need to unchain
*it from the previous Psb.
	T ← (prPsbLink) and T;	*T ← PsbLink.next
	LU ← (prPsbIndex) - T, Call[Requeue1];	*IF prPsbIndex = PsbLink.next
*ELSE PrevLink ← queue.tail
	T ← (prQueue) and T;
FindPrev:
	prPrevPsbIndex ← T;
FetchPrev:	*Fetch PrevPsbIndex↑ into PrevPsbLink.
	PFetch1[prPda,prPrevPsbLink], Call[TGetsPsbIndexMask];
	T ← (prPrevPsbLink) and T;
	LU ← (prPsbIndex) - T;	*IF PrevPsbLink.next # PsbIndex
	GoTo[FindPrev,ALU#0];	*THEN prPrevPsbIndex ← PrevPsbLink.next
*Continue when we have found the preceding Psb. Move the next pointer of the
*Psb being dequeued to the next pointer of the previous Psb.
	prPrevPsbLink ← (prPrevPsbLink) and not T;	*PrevPsbLink.next ← 0
	T ← prNextPsbLink, Call[PrevLinkOrT];	*T ← PsbLink.next
  				*PrevPsbLink.next ← PsbLink.next
	T ← prPrevPsbIndex, Task;
	PStore1[prPda,prPrevPsbLink];	*Store PrevPsbLink.
*Now we have removed the Psb pointed to by PsbIndex from the source queue.
*If we don't know what queue we are on, set the cleanup link.
SetCleanupLink:
	prFlags, GoTo[SourceNotNil,R Even];
*Continue if source is nil. We don't know what queue we are on, so we must
*set the cleanup link. Take PsbLink.next (of the psb being dequeued) and put
*it in the cleanup link.
	T ← prPsbIndexMask;
	prPsbFlags ← (prPsbFlags) and not T;	*Flags.cleanup ← 0
	T ← prNextPsbLink;	*Flags.cleanup ← PsbLink.next
	prPsbFlags ← (prPsbFlags) or T, GoTo[Enqueue];

*Come here if the source queue is not nil. We know what queue we are on.
*If SourceQueue points to the Psb being dequeued, change it to point to the
*previous Psb.
SourceNotNil:
	PFetch1[prQTemp,prQueue,0];	*Fetch SourceQ↑ into Queue.
	T ← prPsbIndexMask;
	T ← (prQueue) and T;		*T ← SourceQ.tail
	LU ← (prPsbIndex) - T;		*IF SourceQ.tail # PsbIndex
*THEN GoTo Enqueue; queue.tail ← 0
	prQueue ← (prQueue) and not T, GoTo[Enqueue,ALU#0];
*Queue.tail ← PrevPsbIndex; store Queue.tail
	  T ← prPrevPsbIndex, Call[OrQueueStore];
Enqueue:	*Now we are ready to insert the Psb into the dest queue.
	Dispatch[prFlags,DestQbit,2], Call[SetQTemp];	*Set QTemp to DestQ
	PFetch1[prQTemp,prQueue,0], Call[TGetsPsbIndexMask];
	T ← (prQueue) and T;		*T ← DestQueue.tail
	prPrevPsbIndex ← T, GoTo[DestQueueNotNil,ALU#0];
*IF DestQueue.tail # nil THEN GoTo RQDestQueueNotNil
*Continue if dest queue is nil. Set the Psb being enqueued to point to itself.
*Then set DestQ to point to the Psb being enqueued.
	T ← prPsbIndexMask;
	prPsbLink ← (prPsbLink) and not T;	*PsbLink.next ← 0
	T ← prPsbIndex, Call[LinkOrT];	*PsbLink.next ← PsbIndex
	T ← prPsbIndexMask, Call[MakeDestQueuePointToPsb];
RequeueExit:
	PFetch1[prPda,prReady,pdaReady!];	*Fetch ReadyQ↑ into Ready.
	T ← prPsbIndex, Call[StorePsb];	*Update Psb
	prFlags ← (prFlags) or (RequeueOccurred), GoTo[ReturnLinkRet];

*Dest queue is not nil. PrevPsbIndex and T contain DestQueue.tail. We must
*insert the Psb into the DestQueue according to priority. First see if the
*priority of the Psb is less than or equal to the priority of the last Psb
*in the DestQueue. If so, we can insert the Psb at the end of the DestQueue.
*Fetch DestQueue.tail↑ into PrevPsbLink.
DestQueueNotNil:
	PFetch1[prPda,prPrevPsbLink], Call[prRet];
	T ← LdF[prPrevPsbLink,1,3];	*T = PrevPsbLink.priority
*IF PrevPsbLink.priority >= Psb.priority THEN GoTo ChainToEndOfQueue
	LU ← (prPsbPriority) - T - 1;
	T ← prPsbIndexMask, GoTo[ChainToEndOfQueue,ALU<0];
*Continue if priority of Psb being enqueued is .ge. priority of the Psb at
*the end of the queue.  This means we cannot add it to the end of the queue.
*We will need to search through the queue and find a place to insert it.
	T ← (prPrevPsbLink) and T;	*T ← PrevPsbLink.next
InsertByPriority:	*Fetch PrevPsbLink.next↑ into NextPsbLink
	PFetch1[prPda,prNextPsbLink], Call[prRet];
	T ← LdF[prNextPsbLink,1,3];	*T ← NextPsbLink.priority
*IF Psb.priority > NextPsbLink.priority THEN GoTo InsertPsb
	LU ← (prPsbPriority) - T - 1;
	T ← prPsbIndexMask, GoTo[InsertPsb,ALU>=0];
	T ← (prPrevPsbLink) and T;	*T ← PrevPsbLink.next
	prPrevPsbIndex ← T, Task;
	T ← prNextPsbLink;
	prPrevPsbLink ← T;
	T ← (prPsbIndexMask) and T, GoTo[InsertByPriority];

*Come here the priority of the Psb to be enqueued is .le. the priority of
*the last item in the queue. Change the queue head to point to the Psb being
*enqueued. We chain the new Psb onto the end of the queue.
*DestQueue.tail ← 0
ChainToEndOfQueue:
	prQueue ← (prQueue) and not T, Call[MakeDestQueuePointToPsbx];
*Come here when the priority of the Psb to be inserted is .gr. the priority
*of the Psb pointed to by PrevPsbLink.next.  Move PrevLink.next to the next
*field of the Psb being inserted.  Change PrevLink.next to point to the Psb
*being inserted.
InsertPsb:
	prPsbLink ← (prPsbLink) and not T;	*PsbLink.next ← 0
*PsbLink.next ← PrevPsbLink.next
	T ← (prPrevPsbLink) and T, Call[LinkOrT];	*T ← PrevPsbLink.next
*Now set PrevLink.next to point to Psb being enqueued.
	T ← prPsbIndexMask, Call[PrevLinkAndNotT];	*PrevPsbLink.next ← 0
	T ← prPsbIndex, Call[PrevLinkOrT];	*PrevPsbLink.next ← PsbIndex
	T ← prPrevPsbIndex;
	PStore1[prPda,prPrevPsbLink], GoTo[RequeueExit];	*Store PrevPsbLink

*Queue contains DestQueue↑, T contains PsbIndexMask. Change DestQueue.tail
*to point to Psb.
MakeDestQueuePointToPsb:
	prQueue ← (prQueue) and not T;	*DestQueue.tail ← 0
MakeDestQueuePointToPsbx:
	T ← prPsbIndex;
OrQueueStore:
	prQueue ← (prQueue) or T;
	PStore1[prQTemp,prQueue,0], GoTo[TGetsPsbIndexMask];

SetQTemp:
	prQTemp ← 0C, Disp[.+1];
	prQTempHi ← 400C, GoTo[TGetsPsbIndexMask], At[QueueDisp,ReadyQbits];

	T ← prMonitorQ, At[QueueDisp,MonitorQbits];
	prQTemp ← T;
	T ← prMonitorQhi, GoTo[SetQTempHi];

	T ← prConditionQ, At[QueueDisp,ConditionQbits];
	prQTemp ← T;
	T ← prConditionQhi;
SetQTempHi:
	prQTempHi ← T, GoTo[TGetsPsbIndexMask];

%This procedure must be invoked before accessing a condition variable queue
since the queue pointer may be incorrect. This occurs when the last Psb of
a CV queue has been moved to another queue and Requeue did not know to which
CV queue the Psb belonged. (This happens when a process times out on a CV
queue or is aborted.) When Requeue detects this situation, it causes the
Psb's cleanup link to have the value of the Psb's old link field--which
should point to the front of the queue. The goal of this subroutine is to
find the correct head of the CV queue, and therefore the tail--to which the
CV should point. We follow the cleanup links til there are no more,
declare the last Psb as the head, and then follow the usual links until the
tail is found.

Input:	ConditionQ	base register pair points to Condition
	Condition	contains ConditionQ↑
	T		PsbIndexMask
Output:	Condition	contains updated ConditionQ↑
	T		contains PsbIndexMask
Temps shared with Requeue Temps
	CleanupLink	used to fetch and store CleanupLink
	ConditionTail	contains Condition.tail
	QueueHead	contains new head of condition queue
	QueueTail	contains new tail of condition queue
Exits:	Return to caller
Timing:	8 cycles when CleanupLink is nil.
%
CleanUpQueue:
	T ← (prCondition) and T;	*T ← condition.tail
*Save condition.tail
	prConditionTail ← T, UseCTask, Skip[ALU#0];
	  GoTo[TGetsPsbIndexMask];	*Empty--return PsbIndexMask
	T ← APCTask&APC, Call[SaveReturnInReturnLink];
*Returns with PsbIndexMask in T.
	T ← (prConditionTail) + (psbFlags), Call[FetchCleanupLink];
*IF flags.cleanup = NIL THEN Return IF Condition.tail = flags.cleanup
	T ← (prCleanupLink) and T;
	LU ← (prConditionTail) - T, GoTo[CleanupLinkEmpty,ALU=0];
*THEN GoTo RemoveSolePsb.  QueueHead ← flags.cleanup
	prQueueHead ← T, GoTo[RemoveSolePsb,ALU=0];
*Search through the chain until we find a cleanup link that is nil. We then
*declare this to be the head of the queue. If we find a cleanup link that
*points to the tail of the queue, then the queue is now empty.
*Fetch flags word of the next entry in the cleanup link chain.
FindCleanupHead:
	T ← (prQueueHead) + (psbFlags), Call[FetchCleanupLink];	*T = PsbIndexMask
*IF flags.cleanup = NIL THEN GoTo FoundHead IF flags.cleanup = QueueHead
	T ← (prCleanupLink) and T;
	LU ← (prQueueHead) - T, GoTo[FoundHead,ALU=0];
	prQueueHead ← T, DblGoTo[FindCleanupHead,RemoveSolePsb,ALU#0];

FoundHead:	*Come here when QueueHead points to the head of the Psb chain.
	T ← MNBR ← prQueueHead;	*MNBR ← head of queue
FindQueueTail:
	prQueueTail ← T, Call[FetchCleanupLink];	*Fetch next link
	prCondition ← (prCondition) and not T;	*condition.tail ← nil
	T ← (prCleanupLink) and T;	*T ← Link.next
	LU ← (MNBR) - T;	*IF Link.next # head
	GoTo[FindQueueTail,ALU#0];
	prCondition ← (prCondition) or T, GoTo[UpdateConditionQueue];	*Set condition.tail

*Come here if the cleanup link in the Psb points to itself.  There was only
*one Psb in the queue, and we must remove it.  Also come here if the cleanup
*link in the Psb points to the last Psb in the Queue.  Make the queue empty.
RemoveSolePsb:	*condition.wakeup ← FALSE.  condition.tail ← nil
	prCondition ← (prCondition) and (abortable);
UpdateConditionQueue:
	PStore1[prConditionQ,prCondition,0], Call[prRet];
ReturnLinkRet:
CleanupLinkEmpty:
	APCTask&APC ← prReturnLink, GoTo[TGetsPsbIndexMask];

FetchCleanupLink:	*Return with PsbIndexMask in T.
	PFetch1[prPda,prCleanupLink], GoTo[TGetsPsbIndexMask];

%Reschedule takes the first (i.e., highest priority) Psb of the ready queue
and configures the machine to run that process. The scheduler is always
invoked if Requeue has moved some process from or to the ready queue. A
process can run until it fails to enter a monitor, waits on a conditon
variable with no wakeups waiting, aborts, or an I/O interrupt causes a higher
priority process to move to the front of the ready queue.

Input:	Ready		contains ReadyQueue↑ if RequeueSub did a requeue.
	LU		prFlags AND RequeueOccurred is pending
	LOCAL		points to local frame
Output:	CurrentPsb	updated to point to head of ready queue
	xfMX		dest link (pointer to Psb) for Xfer
	xfMY		set to zero for Xfer
	xfBrkByte	set to 40400b for Xfer
	MemStat		set to Normal for Fault.Mc
	MDShi		set to prPsbMds
Temps:	The following are shared with RequeueSub temps.
	PsbLink
	State		Base register pair used to reference Pda.state
	StackPointer	used to save stack pointer in SV
	Frame		used to save frame in SV
Subroutines called:
	SavPCInFrame
Exits:	prTail		if no reschedule necessary
	Xfer		if reschedule occurred
	Kfcr		if wakeup error
%
RescheduleIfRequeueOccurred:	*Reschedule only if requeue occurred.
	T ← prCurrentPsb, GoTo[prTail,ALU=0];
Reschedule:	*Always come here with T just set to prCurrentPsb.
*Set up StateHi.  prCurrentPsb = 0 means not running. If not running, don't
*save process.
	prStateHi ← 400C, Skip[ALU#0];
	  GoTo[RSFindRunnable];
*Note that it is always necessary to save a running process, because its
*priority may have been changed.  Fetch the running Psb into prPsbLink,
*prPsbFlags, prPsbContext, prPsbMds.
RSSaveProcess:
	PFetch4[prPda,prPsbLink];
	T ← LOCAL, Task;
*Prepare to save LOCAL in state vector.
	prFrame ← T;
*See if reschedule is due to an interrupt or fault.
	LU ← (prFlags) and (SaveStack);
*Prepare to save LOCAL in Psb.  Need only save the Psb when not preempted.
	prPsbContext ← (Zero) or T, GoTo[RSSavePsb,ALU=0];
*Allocate a state vector for the stack.
	prPsbLink ← (prPsbLink) or (vector);	*Link.vector ← TRUE
*Uses the current priority to return with: (1) T ← prCurrentSAT ← ptr to the
*StateAllocTable entry. (2) prPtrToSV ← ptr to the first stateVector.
	T ← (pdaState), Call[SetState];
	T ← prPtrToSV;
	prState ← T;		*prPsbContext ← ptr to StateVector.
	prPsbContext ← T, GoTo[.+3,ALU#0];	*If there is a StateVector
*If ptr to StateVector is 0, no StateVector is available, a fatal error.
	  LoadPageExternal[0];
	  T ← NoStateVectorError, GoToExternal[CrashLoc];	*MPC = 0116.
*Fetch ptr to next StateVector for this priority.
	PFetch1[prPda,prPtrToSV];
*Store ptr to next StateVector in StateAllocTable.
	T ← prCurrentSAT, Call[StorePtrToSV];
*Even if StkP is zero, we must save at least two stack words, so
*we do one PStore4. We could do subsequent PStores only if StkP > 3, but time
*spent testing reduces the average gain and we are tight on space.
	T ← 377C;
	PStore4[prState,Stack0,svStack!], NonQuadOK, Call[prRet];
	T ← (NStkP) xor T;	*T ← stack pointer
	prStackPointer ← T; 	*prStackPointer ← stack pointer
	PStore4[prState,Stack4,svStack4!], NonQuadOK;
	T ← svData;
	PStore4[prState,Stack8,svStack8!], NonQuadOK, Call[prRet];	*Allow write of T.
	PStore2[prState,prData], Call[prRet];	*Save Data in SV. Only meaningful for faults.
	PStore2[prState,Stack12,svStack12!], OddOK, Call[prRet];
*Save StkP and LOCAL in SV (from prStackPointer and prFrame).
	PStore2[prState,prStackPointer,svWord!];
*Store prPsbLink, prPsbFlags, prPsbContext, prPsbMds into Current Psb.
RSSavePsb:
	LoadPage[xfPage1];	*Even placement; paired with RSSaveProcess+5
	Call[SavPCinFrame];	*Save PC in frame clobbers xfTemp1 (RM 73)
	StkP ← RZero, Call[StoreCurrentPsb];
RSFindRunnable:	*Fetch ReadyQTailPtr
	PFetch1[prPda,prPsbLink,pdaReady!], Call[TGetsPsbIndexMask];
	T ← (prPsbLink) and T, Call[FetchNextPsb];	*Fetch Tail Psb.
	LU ← prReady, Skip;			*To Test For Empty ReadyQ
RSFRLoop:
	LU ← (prReady) xor T;	*End of ReadyQ?
	T ← prPsbIndexMask, Skip[ALU#0];
	  GoTo[NoneReady];	*Yes, and no runnable process found.
	T ← (prPsbLink) and T, Call[FetchNextPsb];
*Uses the current priority to return with: (1) T ← prCurrentSAT ← ptr to
*the StateAllocTable entry. (2) prPtrToSV ← ptr to the first stateVector.
	T ← (pdaState), Call[SetState];
*Link.vector ← FALSE.  IF Link.vector WAS TRUE THEN load state and run this process.
	prPsbLink ← (prPsbLink) and not (vector), GoTo[RSLoadAndFreeState,R Odd];
*StateVector must be available at current priority to run the process.
	LU ← (prPtrToSV);	*StateVector available?
	T ← prCurrentPsb, GoTo[RSFRLoop,ALU=0];	*No, get next process.
*This process is runnable and doesn't need to LoadStack.
*Link.enterFailed ← FALSE.  If not enter failed, goto RSXfer
	LoadPage[opPage0];
	prPsbLink ← (prPsbLink) and not (EnterFailed), GoToP[RSXfer,R>=0];
OnPage[opPage0];
	Stack&+1 ← 0C, GoTo[RSXfer]; 	*Push[FALSE]

OnPage[prPage];
RSLoadAndFreeState:	*Come here with T = prCurrentSAT.
*Store ptr to saved StateVector in StateAllocTable.
	PStore1[prPda,prPsbContext];
	T ← prPsbContext, LoadPage[opPage0];
	prState ← T, GoToP[.+1];
OnPage[opPage0];
*Load Stack0..3.  Alow write of prState
	PFetch4[prPda,Stack0], NonQuadOK, Call[P4Ret];
*Fetch stack pointer and Frame pointer.
	PFetch2[prState,prStackPointer,svWord!];
	PFetch1[prState,prPsbContext,svFrame!], Call[P4Ret];	*Fetch Frame ptr again.
	PFetch4[prState,Stack4,svStack4!], NonQuadOK, Call[P4Ret];
	StkP ← prStackPointer;	*Load stack pointer.
*Store prev. content of SAT in 1st word of freed stateVector to add this
*stateVector to the chain.
	PStore1[prPda,prPtrToSV], Call[P4Ret];
	PFetch4[prState,Stack8,svStack8!], NonQuadOK;	*Load Stack8..11
	PFetch2[prState,Stack12,svStack12!], OddOK;
RSXfer:	T ← prPsbContext, LoadPage[xfPage1];	*Frame pointer of CurrentPsb
	xfMX ← T, LoadPage[prPage];
OnPage[xfPage1];
	LOCAL ← T, CallP[StoreCurrentPsb];	*LOCAL ← destination link.
	T ← prPsbMds, LoadPage[wrMDSPage];
	MDShi ← T, Call[WrMDS1];
	MemStat ← Normal;
	xfBrkByte ← 40400C;
	T ← xfMY ← 0C;	*Source ← nil
	PCB ← 1C, GoTo[Xfer];	*Set PCB to illegal value for Xfer.

OnPage[prPage];

*Enters with T set to the Pda relative offset of the beginning of the
*StateAllocTable.  Establishes SAT entry using the current priority from
*prPsbLink.  Returns with: (1) T ← prCurrentSAT ← ptr to the StateAllocTable
*entry. (2) prPtrToSV ← ptr to the first stateVector or 0 if no StateVector
*available.
*T ← ptr to the StateAllocTable entry for the current priority.
SetState:
	T ← (LdF[prPsbLink,priBitPos,priFldSize]) + T;
*Fetch ptr to first StateVector this priority.
	PFetch1[prPda,prPtrToSV];
*Save it in prCurrentSAT.
	prCurrentSAT ← T, Return;	*Bypass kludge ok

NoneReady:
	LU ← (xfWDC) - 1, LoadPage[opPage0];	*Test Wakeup Disable Count
	prCurrentPsb ← 0C, GoToP[.+3,ALU<0];	*set to not running.
OnPage[opPage0];
	  LoadPage[opPage3];
	  T ← sRescheduleError, GoToP[kfcr];	*IF wdc # 0 THEN WakeError
	T ← (SStkP&NStkP) xor (377C), Call[P4Ret];
*Idle loop
	GoTo[IdleInt,IntPending];
P4Ret:	Return;

OnPage[PrPage];

TGetsFlagsAndT:
	T ← (prPsbFlags) and T, Return;

LinkOrT:
	prPsbLink ← (prPsbLink) or T, Return;

FlagsOrT:
	prPsbFlags ← (prPsbFlags) or T, Return;

TGetsPsbIndexMask:
	T ← prPsbIndexMask, Return;

StoreMonitor:
	PStore1[prMonitorQ,prMonitor,0], GoTo[TGetsPsbIndexMask];

*Return with PsbIndexMask in T.
SaveReturnInReturnLink:
	prReturnLink ← T, GoTo[TGetsPsbIndexMask];

FetchNextPsb:
	prCurrentPsb ← T, Skip;
FetchCurrentPsb:
	T ← prCurrentPsb;
FetchPsb:
	PFetch4[prPda,prPsbLink], GoTo[prRet];

prRet:	Return;

StoreCurrentPsb:
	T ← prCurrentPsb;
StorePsb:
	PStore4[prPda,prPsbLink], GoTo[prRet];

StorePtrToSV:
	PStore1[prPda,prPtrToSV], GoTo[prRet];

PrevLinkAndNotT:
	prPrevPsbLink ← (prPrevPsbLink) and not T, Return;

PrevLinkOrT:
	prPrevPsbLink ← (prPrevPsbLink) or T, Return;

AddTimeout:
	T ← (prPdaTimeout) + T, Return;

%Come here on Page, WriteProtect or Frame faults.

Input:	T		FaultOffset
	prData		Fault Parameter
Output:	prData(1)	For PageFault and WriteProtectFault convert prData to
			LongPtr to faulted page (page portion a 16 bit -1 if
			MapOutOfBounds)
Temps:	prConditionQ	Used as base-reg-ptr to Fault[fi].queue and
			Fault[fi].condition.
	prFlags		SrcQ and DestQ spec. for RequeueSub and NWUXXX.
	prPsbIndex	Tell RequeueSub which Psb to requeue.
Subroutines called:
	RequeueSub
	CleanUpQueue
	NWUXXX
Exit:	Reschedule
%
OnPage[opPage0];

*Indicate SrcQ and DestQ for RequeueSub.
*Set prConditionQ to Fault[fi].queue (pda + offset).
prFault:	*Add Pda to fault offset.
	T ← (prPda) + T, LoadPage[prPage], At[prFaultLoc];
	prConditionQ ← T, CallP[FetchCurrentPsb];
	prFlags ← FaultFlags;
	prPsbIndex ← T, LoadPage[prPage];
*Will requeue faulted process from ReadyQ to "ConditionQ"  because of prFlags.
	prConditionQhi ← 400C, CallP[RequeueSub0];	*400b=PdaHi
*Call NotifyWakeUp with prConditionQ pointing to Fault[fi].condition and
*prFlags set for requeue from ConditionQ to ReadyQ.
*This will be set to ReadyQueue↑ if RequeueSub puts someone on the ReadyQueue.
	prFlags ← InterruptFlags;	*Set to requeue from ConditionQ to ReadyQ.
*Cleanup interrupt[level].condition returns with PsbIndexMask in T.
	PFetch1[prConditionQ,prCondition,1];
	prConditionQ ← (prConditionQ) + 1, LoadPage[prPage], Call[CUQ1];
*NWUXXX goes to WakeHead or returns if queue NIL
	LU ← (prCondition) and T, Call[NWUXXX];
*Does prConditionQ = Fault[frameFault].cond.
	LU ← (prConditionQ) xor (qFrameFaultCOS);
*Frame Fault doesn't convert prData.
	T ← LdF[prData,0,10], GoTo[prFaultRS,ALU=0];

*Convert page number to long pointer in prData(1) for Page or WriteProtect
*Fault.  Note: Reschedule stores prData(1) in State.data.
	prData1 ← T;
	prData ← LSh[prData,10];
prFaultRS:
	LoadPage[prPage];
	prFlags ← (prFlags) or (SaveStack), GoToP[RescheduleCurrent];

CUQ1:	T ← prPsbIndexMask, GoToP[CleanUpQueue];

%Come here from MesaOP0 knowing that NWW#0 (there are wakeups waiting), and
xfWDC = 0 (wakeups are not disabled); we know this because IntPending is set
true by NotifyInterrupt (in Initialize.Mc) only when NWW is made non-zero.
NWW has been zeroed, and WW has been set to the previous contents of NWW.
Now translate bits in WW into naked notifies, each of which moves a process
from a condition variable queue to the ready queue or else sets the
wakeupWaiting bit of the condition variable.

I think that we get here once/field from the UTVFC task (= once per 1/77 sec)
and ? from the RDC task.

Input:	WW		previous contents of NWW
Output:	ConditionQ	updated to point to a Condition in the Pda
	Condition	Contents of ConditionQ↑
	Time		updated if timer interrupt
	Ticks		updated if timer interrupt
	Link		set to Condition.tail↑ for Requeue
Temps:	PsbLink		4-word Psb buffer
	WW		when all levels have been checked, we use this for a
			temporary.
Subroutines called:
	CleanUpQueue
	RequeueSub
	NWUXXX (WakeHead)
Exits:	Reschedule or NoneReady

Timing:	~30 cycles from @NOP to Interrupt
	+13 + Reschedule + NOnes*(31+CleanUpQueue+NWUXXX) + NZeroes*2
		where NZeroes is the number of zeroes in WW to the right of
		the left-most one.  NWUXXX is 5+WakeHead=46 cycles+RequeueSub
		ordinarily and CleanUpQueue is ordinarily 8 cycles, so the
		total subterm is NOnes*(85+RequeueSub).
Average timing seems unimportant except at CheckForTimeoutLoop, where with
150 processes and execution 77/3 times/sec, each cycle is about .0385 percent
of all cycles.
%
OnPage[opPage0];

*This will be set to ReadyQueue↑ if RequeueSub puts someone on the ReadyQueue.
Interrupt:
	PFetch1[prPda,prReady,pdaReady!], Task;
*Set to requeue from ConditionQ to ReadyQ.
	prFlags ← InterruptFlags;
*Start with the last interrupt level.
	prConditionQ ← pdaLastInterrupt;
FindLevel:	*ConditionQhi is the same as PdaHi.
	prConditionQhi ← 400C, Call[.+1];
*Find the interrupt level
	WW ← RSh[WW,1], Skip[R Odd];	*IF wakeup[intLevel]
	  prConditionQ ← (prConditionQ) - (2C), Return;	*Next level
*This level has an interrupt.
	LU ← (prConditionQ) - (pdaInterrupt);	*IF level = 0 THEN
*Check for timeouts ELSE
	T ← (SStkP&NStkP) xor (377C), GoTo[CheckForTimeouts,ALU=0];
	PFetch1[prConditionQ,prCondition,0];
*This code is register critical--WW, prConditionQ/Qhi must survive
*CleanUpQueue, WakeHead, and Requeue.
	LoadPage[prPage], Call[CUQ1];	*Returns PsbIndexMask in T
	LU ← (prCondition) and T, Call[NWUXXX];	*Check condition.tail = nil
*Continue interrupt checking if WW .ne. 0
	LU ← WW;
	prConditionQ ← (prConditionQ) - (2C), DblGoTo[FindLevel,IntExit,ALU#0];

NWUXXX:	LoadPage[prPage], Skip[ALU=0];	*Skip if Queue Nil
	  UseCTask, GoToP[WakeHead];
*condition.wakeup ← TRUE
	prCondition ← (prCondition) or (wakeup), GoToP[.+1];
OnPage[prPage];
	PStore1[prConditionQ,prCondition,0], GoTo[prRet];

OnPage[opPage0];

CheckForTimeouts:
	PFetch1[prPda,prIntPdaTimeout,pdaTimeout!];
	prIntSaveStkP ← IP[prTime]C, Task;
	prIntSaveStkP ← T, StkP ← prIntSaveStkP, NoRegILockOK;
	Stack ← (Stack) - 1;	*prTime ← (prTime) - 1
	PFetch1[prPda,WW,pdaCount!], Skip[ALU=0];	*Fetch Psb count into WW
	  StkP ← prIntSaveStkP, GoTo[IntExit];
*In other words, the timeout scan is done every third field interrupt or
*every .04 seconds with a LF monitor.
	Stack ← 3C;	*prTime ← tickSize
	Stack&+1, Task;
*prTicks ← (prTicks) + 1 [prTicks is at IP[prTime]+1]
	Stack ← (Stack) + 1;
*BEGIN TimeoutScan.
	prPsbIndex ← Sub[pdaBlock!,PsbSize!]C;	*Index of first Psb.
*The timing below here is 23/psb + 4/psb with a timeout +
*(20+RequeueSub)/timeout + 8 + Reschedule.  Typical numbers are 150 processes,
*30 waiting on condition variables (?), 6 of the 30 with timeouts, and 2 or 3
*timing out.
*23 cycles/psb is .88 percent of all cycles with 150 psbs.

	T ← RSh[prPsbIndex,2];
*Low part of prPda base register is 0, so won't carry into high part.
	T ← prIntPdaTimeout ← (prIntPdaTimeout) + T + 1;
CheckForTimeoutLoop:
	PFetch1[prPda,prTimeout], Task;
	prPsbIndex ← (prPsbIndex) + (PsbSize);
	T ← prTimeout;
	LU ← (Stack) - T, GoTo[CheckEnd,ALU=0];
	T ← prPsbIndex, Skip[ALU=0];
	  WW ← (WW) - 1, GoTo[CheckEndx];	*Decrement count
*Zero timeout value.  Prepare to requeue the Psb to the Ready queue.
	PFetch4[prPda,prPsbLink];	*Fetch Psb into 4-word buffer
	prFlags ← (prFlags) or (SourceQNil), Task;
	T ← prIntPdaTimeout;
	PStore1[prPda,RZero];
	LoadPage[prPage];
*This call to Requeue is one of the register-critical places in the code.
*WW, prIntSaveStkP, and prIntPdaTimeout must survive requeue; prConditionQ
*and prConditionQhi are not needed by Requeue for this call.
*Psb.waiting ← FALSE.
	prPsbFlags ← (prPsbFlags) and not (waiting), Call[RequeueSub0];
	WW ← (WW) - 1, GoTo[CheckEndx];	*Decrement count
CheckEnd:
	WW ← (WW) - 1, GoTo[CheckEndx];	*Decrement count
CheckEndx:
	T ← prIntPdaTimeout ← (prIntPdaTimeout) + 1,
		GoTo[CheckForTimeoutLoop,ALU#0];
	StkP ← prIntSaveStkP;
IntExit:
	LU ← prReady, LoadPage[prPage];	*Fetch ready queue into Temp
	prFlags ← (prFlags) or (SaveStack), GoToP[NoneReady,ALU=0];
OnPage[prPage];
	T ← prCurrentPsb, GoTo[Reschedule];

:END[MesaP];