:TITLE[MesaX--Alto.Mode];

%Ed Fiala 27 May 1983: Remove illegal task SETF.
Ed Fiala 3 June 1982: Bum 1 mi at @PORTO, 2 mi at @DESCB, @DESCBS.
%

%Tentative implementation comments:
The frame is freed only on RET and LSTF; only in these cases and on entry
from LoadStateNF is the PC not saved; in all other cases the PC is saved in
the frame.  LOCAL, GLOBAL, and CODE point at quadwords (i.e., low two bits
are 0).  Left and right halves of CODEhi and PCBhi are equal.
LOCALhi = GLOBALhi = MDShi; LOCAL points at a block configured as follows:
	LOCAL-1		FSI for local frame
	LOCAL+0		This frame's GLOBAL
	LOCAL+1		Byte PC saved when this frame Xfers
	LOCAL+2		caller's LOCAL (put in xfMY by SavePCInFrame)
	LOCAL+3		caller's xfMX (?)
	LOCAL+4+n	Local n
Frames on an FSI list are linked through word 0 with pointer to list head in
word -1.

The FSI table is locked into core, so references into it can't page fault;
LOCAL-1 and LOCAL are guaranteed on the same page, so the LOCAL references
by xfer can't page fault--this means that no page fault can occur during
deallocation of the old frame.  Hence, the only reason for EarlyXfer fault
fixup state is so that CODE can be reloaded so that the PC saved by the trap
will be correct--could remove this state by ensuring that PC was already
saved at the onset of any fault.
%

*since xfPage1 has NextData's and NextInsts, it must have refill link at 377
xfRefill:	PFetch4[PCB,IBuf,4], GoToP[MesaRefill], At[xfPage1p,377];

xfRet:	Return;
SaveRLink: xfRLink ← T, Return;
EXMemStat:	MemStat ← EarlyXfer, Return;

SavePCXfer:
	T ← CODE, LoadPage[opPage3];
	T ← (PCB) - T, Call[SPCIF0];	*15 bits, since code segments < 32k.
*xfXTSreg is used for Xfer traps (normally 0)
Xfer:	xfXTSreg ← RSh[xfXTSreg,1], GoTo[XferNTC,R Even]; *Trap check
	  *Cause xfer trap with 0 as reason, xfMX as parameter
	  T ← xfMX, LoadPage[opPage3];
	  xfXTSreg ← 0C, GoToP[XTrap];
XferNTC:
	LU ← Dispatch[xfMX,16,1], Skip[R Odd];	*entry for no trap check
	  T ← xfMX, Disp[XferType0];
	T ← xfGFT, Disp[XferType1];

XferType0:	*Control link in T is frame pointer; save it.
	xfCount ← T, DblGoTo[xfT0a,xfConFault,ALU#0], DispTable[2];
XferType2:	*Indirect control link
	PFetch1[MDS,xfCount], Task;
	T ← xfGFT;
	LU ← Dispatch[xfCount,16,1], Skip[R Odd];
	  T ← xfCount, Disp[XferType0];		*Type 0 or 2
	T ← (LdF[xfCount,0,11]) + T, Disp[.+1];
	T ← (LdF[xfCount,0,11]) + T, Skip, DispTable[2];	*(2*gfi) + gft
	RTemp ← sUnbound, GoTo[StashMX];	*Type 3
	PFetch2[MDS,xfTemp], Call[EXMemStat];	*Type 1
	xfCount ← (LdF[xfCount,11,6]) + 1, GoTo[xfT1a];

xfConFault:	*Control fault if control link = 0.  MB => don't free frame
	RTemp ← sControlFault, DblGoTo[QTrap,QTrapF,MB];

xfT0a:	PFetch2[MDS,xfTemp], Call[EXMemStat];	*Fetch G and PC
	T ← (LOCAL) - 1, Skip[MB];
	  PFetch1[MDS,xfFSI];		*Start freeing the current frame
					*LOCAL[-1] on same page as LOCAL[0],
					*so this reference won't page fault.
	T ← GLOBAL;
	T ← (xfTemp) xor T;		*Compare new G to old G
	T ← GLOBAL ← (GLOBAL) xor T, GoTo[CValid,ALU=0];
	  Skip[ALU#0];
	    RTemp ← sUnbound, GoTo[StashMX];	*New G = 0, trap
*This reference might page fault--if it does, GLOBAL and CODEhi are smashed.
	  PFetch4[MDS,IBuf], Call[LoadC];	*Fetch global frame overhead
	  xfGFIWord ← T;

*Finish freeing the current frame if required.
CValid:	T ← (xfFSI) + (xfAV), GoTo[FreeDone,MB];
	PFetch1[MDS,xBuf];		*fetch list head (won't page fault)
*Store list head in Local[0]; garbage in other 3 words but don't care
	PStore4[LOCAL,xBuf,0], Call[xfRet];	*Won't page fault
	PStore1[MDS,LOCAL];		*Store LOCAL into list head
					*(won't page fault)
FreeDone:
	T ← (LSh[xfTemp1,1]) - 1, Skip[R>=0];
	  xfTemp1 ← (Zero) - T, Skip;
	  xfTemp1 ← (Zero) + T + 1;
	PCF ← xfTemp1, Task;
	MemStat ← XferFixup;
	T ← xfCount;
	LOCAL ← T, LoadPage[opPage3];
	T ← RSh[xfTemp1,1], GoToP[XferGO];

*Control Link is a procedure descriptor (158 cycles minimum to completion)
XferType1:
	T ← (LdF[xfMX,0,11]) + T, Skip, DispTable[2];	*T ← gfi + gft
XferType3:	*Control link is unbound whatsis
	RTemp ← sUnbound, GoTo[StashMX];

	T ← (LdF[xfMX,0,11]) + T;	*2*gfi + gft
	PFetch2[MDS,xfTemp], Call[EXMemStat];	*Fetch G & entry vector offset
	T ← (LdF[xfMX,11,6]) + 1;	*2*EVI + 1 since type = 01
	xfCount ← T;
xfT1a:	T ← xfTemp;			*New G
	PFetch4[MDS,IBuf], Skip[ALU#0];	*Fetch the global frame overhead
	  RTemp ← sUnbound, GoTo[StashMX];	*Trap
	GLOBAL ← T, Call[LoadC];
	T ← LSh[xfTemp1,1];
	T ← xfCount ← (xfCount) + T + 1, LoadPage[opPage3];	*xfCount ← 2*EVI + 2
	PFetch2[CODE,xfTemp], GoToP[.+1];	*Fetch PC and FSI
OnPage[opPage3];
	T ← IBuf;
	xfGFIWord ← T;
LFCEntry:
	T ← xfAV;
	T ← (RHMask[xfTemp1]) + T, GoTo[xAlloc]; *Get a frame
AllocRetx:
	xfTemp ← LSh[xfTemp,1];		*Form byte PC
	MNBR ← LOCAL, LOCAL ← T, NoRegILockOK;
	MemStat ← XferFixup;
	PCF ← xfTemp;
	PStore4[LOCAL,GLOBAL,0], Skip[MB];	*Init frame (Can't fault)
	  T ← (MNBR) - 1, Call[Free];
	T ← RSh[xfTemp,1];
*Each cycle from here down represents ~ 0.15% performance slowdown
XferGO:	PFetch4[CODE,IBuf];	*Enter here from XferType0
	PCB ← T;		*bypass kludge
	PCB ← (PCB) and not (3C);
:IF[CacheLocals]; *************************************
	PFetch4[LOCAL,LocalCache0,4];
:ENDIF; ***********************************************
	T ← CODEhi;		*Allow page fault to happen before LoadPage
	PCBhi ← T, LoadPage[0];
	IBuf ← LCy[IBuf,10], Call[SwapBytes1];
	LU ← (xfBrkByte) - (40400C);	*40400b = 2001b rcy 2 for dispatch
	MemStat ← Normal, Skip[ALU=0];
	  SkipData, Call[DoBB];		*Skip next bytecode in IBuf
**Could use NextInst on the FIRST byte, but not after any Nops.
*Even if IntPending is false, NextInst can't be used here because its NIRet
*might cause a task switch that will result in IntPending being set true
*before the next bytecode (which might be NOP) tests IntPending.
DispMan:
	T ← NextData[IBuf];
	xfBrkByte ← (xfBrkByte) or T, Skip[ALU#0];	*Skip NOPs
	  T ← NextData[IBuf], Call[.-1];
DoBB:	xfBrkByte ← LCy[xfBrkByte,2];
	APCTask&APC ← xfBrkByte;
FixxfBrkByte:
	xfBrkByte ← 40400C, Return;

OnPage[xfPage1];

*Load the C register from the global frame information in IBuf..IBuf2
LoadC:	T ← MDShi;
	CODEhi ← T;
***Not sure whether or not CODEhi has to be restored on trap here***
	T ← IBuf1, Skip[R Even];
	  RTemp ← sCSegSwappedOut, GoTo[StashMX];
	LU ← LdF[IBuf2,0,10];
	CODE ← T, GoTo[LoadCX,ALU#0];	*Done if short C (CODEhi←MDShi)
	T ← RHMask[IBuf2];		*Otherwise, same pointer in LH and RH
	CODEhi ← T, Skip[H2Bit8'];
	  CODEhi ← T ← (CODEhi) or (100C);	*Set bits 1 and 9 if out-of-bounds
	CODEhi ← (LSh[CODEhi,10]) or T;
LoadCX:	T ← IBuf, Return;		*Return GFIWord in T

OnPage[opPage3];

*Return with frame in T to P7PushT if MemStat.0 = 1, else to AllocRetx.
*Entry from @ALLOC with FSI in T; also loop here for frame type 3 (indirect).
Alloc:	T ← (LSh[R400,1]) + T;	*Know that xfAV = 1000b = LSh[R400,1]

*Entry here from Xfer with MemStat.0 = 0
xAlloc:	PFetch1[MDS,xfFrame], Task;	*the head of the list (can't fault)
	xfTemp1 ← T;
	LU ← LdF[xfFrame,16,1], Skip[R Odd];
	  T ← xfFrame, DblGoTo[FrType2,FrType0,ALU#0];
	T ← RSh[xfFrame,2], DblGoTo[Alloc,FrType1,ALU#0];

FrType0:
	PFetch1[MDS,RTemp1];	*Fetch Frame[0]
	T ← xfTemp1;
	PStore1[MDS,RTemp1];	*Store into head of list
	T ← xfFrame;
	MemStat ← (MemStat) and not (100000C), DblGoTo[P7PushT,AllocRetx,R<0];

FrType2:
	T ← RSh[xfFrame,2], GoTo[Alloc];	*Indirect

FrType1:	*Trap--check for call from @ALLOC
	MemStat ← (MemStat) and not (100000C), DblGoTo[AATrap,XATrap,R<0];

AATrap:	xfATPreg ← LSh[xfATPreg,2], Call[SavePCInFrame]; *call was from @ALLOC
	LoadPage[xfPage1];
	RTemp ← sAllocListEmpty, GoTo[QTrap]; *don't free frame

XATrap:	T ← xfMX;		*call was from Xfer - check for LFC
	GoTo[.+3,ALU=0];
DoAllocTrap:
	  xfATPreg ← T, LoadPage[xfPage1];
	  RTemp ← sAllocListEmpty, DblGoTo[QTrap,QTrapF,MB];
	T ← (xfGFIWord) and not (177C);
	xfCount ← (LSh[xfCount,1]) + T;	*LFC trap.  Fab procedure descriptor
					* + is important - don't use OR
	T ← xfCount ← (xfCount) - (3C), GoTo[DoAllocTrap];


*SUBROUTINE Free frees the frame at T+1; T must have been loaded in mi that
*does call (Timing ~ 56 cycles).
Free:	PFetch1[MDS,xfFSI];	*get the frame's FSI
Free0:	xfFrame ← T, UseCTask;	*bypass kludge--depends on MDS being 0
	T ← APCTask&APC, Task;
	xfRLink ← T;
	xfFSI ← T ← (xfFSI) + (xfAV);
	PFetch1[MDS,xBuf];	*Fetch list head
	T ← 100C;
	T ← xfFrame ← (xfFrame) + 1, SALUF ← T;
*Store head into frame--trash next 3 words but don't care
	PStore4[MDS,xBuf];
	T ← xfFSI;
	PStore1[MDS,xfFrame];	*Store frame into head
	APCTask&APC ← xfRLink, GoTo[P7Ret];

*Apparently this procedure receives a pointer in xfTemp and stores state
*as follows:
*	xfTemp+MaxStack+1/		LOCAL
*	xfTemp+MaxStack/		StkP
*	xfTemp+(MaxStack-1) to +0	Stack words

OnPage[xfPage1];

SaveState:			*UseCTask in calling instruction
	T ← APCTask&APC, Call[SaveRLink];	*save link in rlink
	T ← (xfTemp) + (Add[MaxStack!,1]C);
	PStore1[MDS,LOCAL], Call[sv377];
	T ← (NStkP) xor T;
	xfTemp2 ← T;
	T ← (xfTemp) + (MaxStack);
	PStore1[MDS,xfTemp2];	*Store StkP
	T ← (xfTemp2) - (Sub[MaxStack!,1]C);
	xfTemp1 ← MaxStack, Skip[Carry];
*Stack depth + 2 = MaxStack+(d-(MaxStack-1))+1
	  xfTemp1 ← (xfTemp1) + T + 1;
	T ← (StkP ← xfTemp1) - 1, Call[svpop];
*Loop returns here
	T ← (NStkP) xor T;
	T ← (AllOnes) + T, Skip[ALU#0];	*T ← offset in saved Stack
	  APCTask&APC ← xfRlink, GoTo[xfRet];
svpop:	T ← (xfTemp) + T;	*T ← xfTemp + StkP - 1
	PStore1[MDS,Stack];
sv377:	T ← 377C, Return;	*T ← true stack pointer


*Entry from Process mechanism and MStart. Ensure no frame freeing.
LoadStateNF: T ← 100C;
	SALUF ← T; 
LoadState:
	T ← (xfTemp) + (MaxStack);
	PFetch1[MDS,xfBrkByte], Task;	*xfBrkByte ← new StkP
	T ← (xfTemp) + (Add[MaxStack!,1]C);
	NWW ← (NWW) and not (100000C);
	PFetch1[MDS,xfMX];		*xfMX ← new LOCAL
	T ← (xfTemp) + (Add[MaxStack!,2]C);
	StkP ← RZero;
	PFetch1[MDS,xfMY];
	T ← (xfBrkByte) and (17C);
	IBuf ← T, Task;		*Stack depth saved for StkP ← below
	xfTemp1 ← MaxStack;
*Check for MaxStack-1 or MaxStack, T ← d - (MaxStack-1)
	T ← (IBuf) - (Sub[MaxStack!,1]C);
	xfBrkByte ← RSh[xfBrkByte,10], Skip[Carry];
*Stack depth + 2 = MaxStack+(d-(MaxStack-1))+1
	  xfTemp1 ← (xfTemp1) + T + 1;
	xfBrkByte ← (xfBrkByte) or (40400C);	*(BrkByte*4 or 2001b) rcy 2
	T ← (xfTemp) - 1, Call[.+1];
*Loop here
	xfTemp1 ← (xfTemp1) - 1;
	T ← (Zero) + T + 1, Skip[ALU>=0];
	  StkP ← IBuf, GoTo[Xfer];
	PFetch1[MDS,Stack], Return;	*Loop

*In general, we want to call Free after all possible Xfer page faults
*can occur, but before all other traps.

*Unbound & CSegSwappedOut Traps come here
StashMX:T ← xfMX;	*RTemp holds SD index (through Free)
	xfOTPreg ← T, DblGoTo[QTrap,QTrapF,MB];

*XferTrap, AllocTrap, & Control Traps go here to free the frame, else to QTrap
QTrapF:	T ← (LOCAL) - 1, LoadPage[opPage3], Call[FreeX];
QTrap:	RTemp ← (RTemp) + (xfAV), Task;
	T ← (RTemp) + (xfSDOffset);
	PFetch1[MDS,xfMX], GoTo[Xfer];

FreeX:	PFetch1[MDS,xfFSI], GoToP[Free0];

OnPage[MStartPage];

*Start from Nova.  xfWDC not initialized???
MStart:	xfTemp ← T;		*Pointer to State for LoadState
	T ← MDShi;		*Initialize some Mesa Emulator registers
	GLOBALhi ← T;
	GLOBAL ← 1C;		*Clobber G so C will be reloaded at the 1st Xfer
	LOCALhi ← T;
	MemStat ← T ← 0C;
	xfMX ← 1C;
	NWW ← T, LoadPage[opPage3];	*Wipe out pending interrupts
	TickCount ← 3C, Call[FFaultStack];
	Stack ← (Stack) or (1C);	*FFault ← "trap on page fault"
	xfXTSReg ← T, LoadPage[xfPage1];
	LOCAL ← 0C, GoToP[LoadStateNF];

OnPage[opPage3];

FFaultStack:
	RTemp ← IP[FFault]C;
FFS1:	StkP ← RTemp, RTemp ← T, NoRegILockOK, Return;


*CODEhi and PCBhi are equal, so we only need to worry about the low word.
*Compute byte PC (relative to CODE) of the opcode to be executed when this
*frame next runs.

SavePCInFrame:
	T ← CODE;
	T ← (PCB) - T;	*15 bits, since code segments are < 32k.
SPCIF0:	T ← (PCF.word) + T, Skip[R Even];
	  RTemp1 ← (Zero) - T, Skip;
	RTemp1 ← T;
	PStore1[LOCAL,RTemp1,1];
SPCIF1:	T ← 100C;		*Set MB
	T ← LOCAL, SALUF ← T;
	xfMY ← T, Return;

MesaRefill7:	PFetch4[PCB,IBuf,4], GoToP[MesaRefill], At[3777];

P7Tail:	LU ← NextInst[IBuf], At[P7TailLoc];
P7Tailx:MemStat ← Normal, NIRet;


*External function calls
efcr:	xfGFIWord, LoadPage[xfPage1], Skip[R Even];
	  PFetch1[CODE,xfMX], GoToP[SavePCXfer];
	PFetch1[GLOBAL,xfMX], GoToP[SavePCXfer];

@EFC0:	T ← (RZero) - (1C), GoTo[efcr], Opcode[300];
	T ← (RZero) - (2C), GoTo[efcr], Opcode[301];
	T ← (RZero) - (3C), GoTo[efcr], Opcode[302];
	T ← (RZero) - (4C), GoTo[efcr], Opcode[303];
	T ← (RZero) - (5C), GoTo[efcr], Opcode[304];
	T ← (RZero) - (6C), GoTo[efcr], Opcode[305];
	T ← (RZero) - (7C), GoTo[efcr], Opcode[306];
	T ← (RZero) - (10C), GoTo[efcr], Opcode[307];
	T ← (RZero) - (11C), GoTo[efcr], Opcode[310];
	T ← (RZero) - (12C), GoTo[efcr], Opcode[311];
	T ← (RZero) - (13C), GoTo[efcr], Opcode[312];
	T ← (RZero) - (14C), GoTo[efcr], Opcode[313];
	T ← (RZero) - (15C), GoTo[efcr], Opcode[314];
	T ← (RZero) - (16C), GoTo[efcr], Opcode[315];
	T ← (RZero) - (17C), GoTo[efcr], Opcode[316];
	T ← (RZero) - (20C), GoTo[efcr], Opcode[317];
@EFCB:	T ← NextData[IBuf] + 1, Opcode[320];
	T ← (Zero) - T, GoTo[efcr];

*Local function calls
lfcr:	PFetch2[CODE,xfTemp], Call[SavePCInFrame];
	xfXTSreg ← RSh[xfXTSreg,1], Skip[R Odd];
	  xfMX ← Zero, GoTo[LFCEntry];	*in XferType1
*Cause trap with reason of 400, parameter of xfCount
	xfXTSreg ← 400C;
	T ← xfCount, GoTo[XTrap];

@LFC1:	T ← xfCount ←  4C, GoTo[lfcr], Opcode[321];
	T ← xfCount ←  6C, GoTo[lfcr], Opcode[322];
	T ← xfCount ← 10C, GoTo[lfcr], Opcode[323];
	T ← xfCount ← 12C, GoTo[lfcr], Opcode[324];
	T ← xfCount ← 14C, GoTo[lfcr], Opcode[325];
	T ← xfCount ← 16C, GoTo[lfcr], Opcode[326];
	T ← xfCount ← 20C, GoTo[lfcr], Opcode[327];
	T ← xfCount ← 22C, GoTo[lfcr], Opcode[330];
	T ← xfCount ← 24C, GoTo[lfcr], Opcode[331];
	T ← xfCount ← 26C, GoTo[lfcr], Opcode[332];
	T ← xfCount ← 30C, GoTo[lfcr], Opcode[333];
	T ← xfCount ← 32C, GoTo[lfcr], Opcode[334];
	T ← xfCount ← 34C, GoTo[lfcr], Opcode[335];
	T ← xfCount ← 36C, GoTo[lfcr], Opcode[336];
	T ← xfCount ← 40C, GoTo[lfcr], Opcode[337];
	T ← xfCount ← 42C, GoTo[lfcr], Opcode[340];
@LFCB:	T ← (NextData[IBuf]) + 1, Opcode[341];
	xfCount ← T;
	T ← xfCount ← LSh[xfCount,1], GoTo[lfcr];

*Stack function call
@SFC:	T ← Stack&-1, LoadPage[xfPage1], Opcode[342];
	xfMX ← T, GoToP[SavePCXfer];

@RET:	PFetch1[LOCAL,xfMX,2], Opcode[343];  *fetch Return link
	xfXTSreg ← RSh[xfXTSreg,1], GoTo[RetTrap,R Odd];
	T ← RZero, LoadPage[xfPage1];
	xfMY ← SALUF ← T, GoToP[XferNTC]; *MB=0  => free frame

RetTrap:T ← 100C;
	SALUF ← T;		*If RET traps, the frame is NOT freed
	T ← (LOCAL) + (6C);
	xfXTSreg ← 1000C;
XTrap:	xfXTPreg ← T, LoadPage[xfPage1];
	RTemp ← sXferTrap, DblGoToP[QTrap,QTrapF,MB];

@LLKB:	T ← NextData[IBuf], Opcode[344];
*xfGFIWord was set up by LoadC when this frame became current.
	T ← (Zero) - T - 1, xfGFIWord, Skip[R Even];
	  PFetch1[CODE,Stack], GoTo[P7Tail];	*Code link
	PFetch1[GLOBAL,Stack], GoTo[P7Tail];	*Frame link

@PORTO:	Call[SavePCInFrame], Opcode[345];
	T ← (Stack&-1) + 1;
	PFetch1[MDS,xfMX], Task;
	T ← (AllOnes) + T;
	xfMY ← T, LoadPage[xfPage1];
	PStore1[MDS,LOCAL], GoToP[Xfer];

@PORTI:	LU ← xfMY, Opcode[346];	
	T ← xfMX, GoTo[portinz,ALU=0];
	PStore1[MDS,RZero], Call[P7Ret];
	T ← (xfMX) + 1;
portinz:
	PStore1[MDS,xfMY];
RefillLocalCache:	*in case the port was in the active frame
	PFetch4[LOCAL,LocalCache0,4], GoTo[P7Tail];

@KFCB:	T ← NextData[IBuf], Opcode[347];
kfcr:	RTemp ← T, Call[SavePCInFrame], At[KFCRLoc];
	LoadPage[xfPage1];
	GoTo[QTrap];

@DESCB:	T ← (xfGFIWord) and not (177C), Opcode[350];
descbcom:
	T ← (MNBR ← NextData[IBuf]) + T;
	T ← (MNBR) + T + 1, GoTo[P7PushT];

@DESCBS:
	T ← (Stack&-1) + (xfGFIOffset), Task, Opcode[351];
	PFetch1[MDS,RTemp];
	T ← (RTemp) and not (177C), GoTo[descbcom];

@BLT:	LP ← 0C, Opcode[352];
	T ← MDShi, LoadPage[BLTPage];
BLTcom:	LPhi ← T, GoToP[.+1];
OnPage[BLTPage];
*fixup: fetch => count + 1; store => source-1, dest-1, count+1
	MemStat ← BltFixup, Call[BLTx]; * set Return address to BLTloop;

BLTloop:LU ← Stack&-1;
	T ← Stack&+1, GoTo[BLTdone,ALU=0]; *get source, point to count
	Stack ← (Stack) - 1;	*decrement count
	PFetch1[LP,RTemp];
	Stack&+1;		*point to dest
	T ← Stack&-2;		*get dest, point to source
	PStore1[MDS,RTemp];
	Stack ← (Stack) + 1;	*increment source
	Stack&+2;
	Stack ← (Stack) + 1, GoTo[BLTint,IntPending]; *increment dest
BLTx:	Stack&-1, Return;	*point to count, Return to BLTloop

BLTdone:Stack&-2;
BLTdonex:	LoadPage[opPage3];
	PFetch4[LOCAL,LocalCache0,4], GoToP[P7Tail];

BLTint:	T ← (RZero) + 1;
BLTstop:LoadPage[opPage0];
	PFetch4[LOCAL,LocalCache0,4], GoToP[NOPint];

@BLTL:	T ← (Stack&-1) and (377C), Opcode[353];
	LPdesthi ← T, LoadPage[BLTPage];
	T ← LPdesthi ← (LSh[LPdesthi,10]) + T + 1, GoToP[.+1];
OnPage[BLTPage];
	LPdesthi ← (FixVA[LPdesthi]) or T;
	T ← Stack&-2, LoadPage[opPage1];
	LPdest ← T, CallP[StackLP];
	RTemp1 ← Zero;
	MemStat ← BltLFixup;	*fixup: source+T, dest+T, count+1
	Stack&+3, Call[BLTLloop];	*point to count
BLTLloop:	LU ← Stack;	*read count, point to source lo
	T ← RTemp1, GoTo[BLTLdone,ALU=0];
	PFetch1[LP,RTemp];
	Stack ← (Stack) - 1;	*decrement count
	RTemp1 ← (RTemp1) + 1;	*increment offset
	PStore1[LPdest,RTemp];
	GoTo[BLTLint,IntPending];
	Return;			*goes to BLTLloop

BLTLdone:
	Stack&-3, GoTo[BLTdonex];

BLTLint:
	Stack&-2;
	Call[BLTLbump];		*wait for page fault before updating Stack
	Stack&+2, Call[BLTLbump];
	T ← (RZero) + 1, GoTo[BLTstop];

BLTLbump:
	Stack ← (Stack) + T + 1;
	Stack&+1, FreezeResult;
	Stack ← (Stack) + 1, UseCOutAsCIn, Return;

@BLTC:	T ← CODE, Opcode[354];
	LP ← T;
	T ← CODEhi, LoadPage[BLTPage], GoToP[BLTcom];

@BLTCL:	T ← sUnimplemented, GoTo[kfcr], Opcode[355];

@ALLOC:	MemStat ← 100000C, Opcode[356];
	T ← Stack&-1;
	xfATPreg ← T, GoTo[Alloc]; *set up in case trap occurs

P7PushT:	Stack&+1 ← T, GoTo[P7Tail];
P7Ret:	Return;


@FREE:	T ← (Stack&-1) - 1, Call[Free], Opcode[357];
	LU ← NextInst[IBuf], Call[P7Tailx];

*Increment Wakeup Disable Counter (Disable Interrupts)
@IWDC:	xfWDC ← (xfWDC) + 1, GoTo[P7Tail], Opcode[360];

*Decrement Wakeup Disable Counter (Enable Interrupts)
@DWDC:	T ← (R400) or (52C), Opcode[361];
	PFetch1[MDS,xfTemp], Call[FixxfBrkByte];
	T ← xfTemp;
	NWW ← (NWW) or T;
***This code is very similar to MIPend, SetClrRS232, and DoInt***
	RTemp ← IP[RSImage]C, GoTo[DWDCnone,ALU=0];	*see if any interrupts
	T ← (SStkP&NStkP) xor (377C), Call[FFS1];	*Exchange StkP/RTemp
	T ← Stack ← (Stack) or (IntPendingBit);		*set IntPending
	StkP ← RTemp, RS232 ← T;
DWDCnone:	xfWDC ← (xfWDC) - 1, GoTo[DispMan];

@STOP:	NWW ← (NWW) or (100000C), Call[SavePCInFrame], Opcode[362];
	T ← CurrentState;
	PFetch1[MDS,xfTemp];
	LoadPage[xfPage1];
	UseCTask, CallP[SaveState];
	PCB ← StopStopPC, Call[FFaultStack];
*FFault ← "crash on page fault"
	LoadPage[neStartPage];
	Stack ← (Stack) and not (1C), GoToP[StartNova];

CATCH:	SkipData, Call[P7Tail], Opcode[363];

*MISC - extended opcodes accessed by dispatching on alpha
@MISC:	T ← MNBR ← NextData[IBuf], Opcode[364];
	RTemp ← T, LoadPage[xfPage1];
	Dispatch[RTemp,12,2], GoToP[.+1];
OnPage[xfPage1];
	Dispatch[RTemp,14,4], Disp[.+1];

	Disp[@ASSOC], At[MiscDisp0,0];			*dispatch for alpha = 0 to 17b
	xfOTPreg ← T, GoTo[FlPnt], At[MiscDisp0,1];		*20b to 37b floating point
	T ← sUnimplemented, GoTo[MiscTrap], At[MiscDisp0,2];	*40b to 57b undefined
	xfOTPreg ← T, GoTo[Cedar], At[MiscDisp0,3];	*60b to 77b Cedar

*Push alpha byte and trap for floating point or Cedar opcodes.
**Note: FP microcode, when loaded, overwrites this mi and the one preceding it.
FlPnt:	T ← sFloatingPoint, GoTo[MiscTrap], At[MiscDisp0,17];
Cedar:	T ← sCedarTrap, GoTo[MiscTrap], At[MiscDisp0,16];

*Associate - TOS contains map entry, (TOS-1) contains VP which is to get it.
@ASSOC:	T ← (Stack&-1) and not (100000C), At[MiscDisp1,0];
	xBuf ← T, Call[MapLP];
ASSOC1:	XMap[LP,xBuf,0], GoTo[MiscTail];

*Set Flags
@SETF:	T ← (Stack&-1) and not (100000C), At[MiscDisp1,1];
	xBuf ← T, Call[MapLP];
	XMap[LP,xBuf,0];
	T ← LSh[xBuf3,10];		*Put flags,,card,blk0 in left byte
	T ← xBuf1 ← (RHMask[xBuf1]) or T; *blk1,rowaddr in low byte
*push old flags & page
	T ← (RZero) or not T, UseCTask, Call[StackGetsT];
	LU ← (LdF[xBuf3,11,3]) - 1; 	*=0 if map entry = VACANT
	xBuf ← (xBuf) and (70000C), Skip[ALU#0];	*isolate new flags, ignore LogSE
	xBuf ← T, GoTo[ASSOC1];		*Vacant entry, use old flags, oldpage
	T ← (Stack) and not (170000C);	*Get old page number
	xBuf ← (xBuf) or T, GoTo[ASSOC1];	*new flags, old page

*Subroutine MapLP creates a base reg pair from a virtual page number for the Map opcodes.
MapLP:	T ← LSh[Stack,10];
	LP ← T;		*Set low Base
	T ← LHMask[Stack&-1];
	LPhi ← T, GoTo[xfRet,ALU>=0];	*Set high byte of high base
	LPhi ← (LPhi) or (40000C), GoTo[xfRet];	*set bit 1 if 0 is set.

*Read & Write Ram format: Stack=40:43,,addr, (Stack-1)=40:43, (Stack-2)=0:17, (Stack-3)=20:37.
@ReadRam:	T ← LdF[Stack&-1,4,14], At[MiscDisp1,2];	*get address
	RTemp ← T;
	T ← 1C, Call[CSRead];	*read 20:37
	T ← 0C, Call[CSRead];	*read 0:17 
	T ← 3C, Call[CSRead];	*read 40:43
	T ← RTemp; 
	Stack ← (LSh[Stack,14]) or T, GoTo[MiscTail];

*Subroutine CSRead reads control store for ReadRam opcode.
CSRead:	APCTask&APC ← RTemp;
	ReadCS;
	T ← CSData, DispTable[1,1,0]; *successor of CSOp must be even
StackGetsT:
	Stack&+1 ← T, Return;

MC[VersionID,0]; *Checks compatibility with LRJ'd code.

@LoadRamJ:
	T ← (Stack&-1) xor (1C), At[MiscDisp1,3];
	RTemp1 ← T, LoadPage[opPage1];	*save bits, jump complemented
	T ← (Stack&-1) and (377C), CallP[StackLPx];
	PFetch1[LP,RTemp,0], Call[MiscRet];
	LU ← (RTemp) xor (VersionID);
	T ← sUnimplemented, GoTo[MiscTrap,ALU#0];
	LoadPage[opPage3];
	T ← (SStkP&NStkP) xor (377C), Call[FFaultStack];
*Make MC1/StkOvf errors crash rather than notifying emulator
	Stack ← (Stack) and not (1C);
	RTemp1 ← T ← (RTemp1) and (1C);		*get jump flag (1 => no jump)
	xfTemp1 ← T, LoadPageExternal[LRJpage]; *allow Tasking if not jumping
	StkP ← RTemp, GoToExternal[LRJStart];

MiscRet:	Return;

MiscTrap:	LoadPage[opPage3];
	GoToP[kfcr];

	T ← sUnimplemented, GoTo[MiscTrap], At[MiscDisp1,4];

*Opcodes for Mesa Input/Output.
*Stack[0:7]=XXX, Stack[10:13]=task no., Stack[14:17]=I/O register number.

@INPUT:	T ← Stack&-1, At[MiscDisp1,5];
	Input[Stack], GoTo[MiscTail];

@OUTPUT:	T ← Stack&-1, At[MiscDisp1,6];
	Output[Stack], GoTo[MiscTail];
*	UseCTask, Call[xfRet];
*	GoTo[MiscTail];

*Checksum Stack1 words starting at Stack2,,Stack3 with the checksum
*accumulated in Stack0; algorithm is CSum ← (CSum + Word) lcy 1.  At entry
*StkP points at Stack3; at exit StkP points at Stack0 (contains csum); if
*Stack0 result was -1, it is changed to 0.
@CSum:	T ← Stack&-1, LoadPage[opPage1], At[MiscDisp1,7];
	LPhi ← T, LoadPage[opPage0], CallP[StackLPy];
*StackLPy returns after LP,,LPhi ← Stack2,,Stack3 with stack popped twice,
*LPhi bounds-checked and in base register format.
	LU ← Stack&+1, LoadPage[CSPage];
	PFetch4[LP,xBuf,0], DblGoToP[CSBeg,CSEnd,ALU#0];

OnPage[CSPage];
*Possible page fault after next mi, so no Stack changes until it is completed.
CSLoop:	Dispatch[Stack2,16,2], GoTo[.+3,Carry'];
	  LPhi ← (LPhi) + (400C) + 1;	*64k boundary crossing
	  Stack3 ← (Stack3) + 1, GoTo[.-2];
	Stack2 ← T, Disp[.+1];
	T ← LCy[xBuf,1], Call[CSWord], DispTable[4];
	T ← LCy[xBuf1,1], Call[CSWord];
	T ← LCy[xBuf2,1], Call[CSWord];
	T ← LCy[xBuf3,1], Call[CSWord];
	PFetch4[LP,xBuf,0];
CSBeg:	LP ← (LP) or (3C);	*Compute address of next quadword
	T ← LP ← (LP) + 1, GoTo[CSLoop,IntPending'];
**THIS LOADPAGE IS TOO SOON.
	Stack&+1, LoadPage[opPage0];
	T ← 2C, GoToP[NOPint];

CSWord:	Stack1 ← (Stack1) - 1;
	Stack0 ← (LCy[Stack0,1]) + T, Skip[ALU=0];
	  Stack0 ← (Stack0) + 1, UseCOutAsCIn, Return;
	Stack0 ← (Stack0) + 1, UseCOutAsCIn;
CSEnd:	LU ← (Stack0) xnor (0C);
	LoadPage[opPage3], Skip[ALU#0];
	  Stack&-2 ← 0C, GoToP[P7Tail];
	Stack&-2, GoToP[P7Tail];

*SetMaintenancePanel opcode; just put value on Stack
@SetMP:	T ← Stack&-1, LoadPage[PNIPPage], At[MiscDisp1,10];
	CallP[PNIP];
MiscTail:	LU ← NextInst[IBuf];
MiscTailx:	NIRet;


*Read realtime clock (push[RM325]; push[MM430];
@RCLK:	LoadPage[XMiscPage], At[MiscDisp1,11];
	T ← (R400) or (30C), CallP[MXRClk];
	Stack&+1 ← T;			*Push[RM 325]
	T ← RTemp, GoTo[MiscPushT];	*Push [VM 430];

@RPRINTER:
	T ← Printer, GoTo[MiscPushT], At[MiscDisp1,12];

@WPRINTER:
	Printer ← Stack&-1, GoTo[MiscTail], At[MiscDisp1,13];

*Misc 14 is defined in MesaIO.Mc as the floating point board kludge io
*opcode, as the CCA kludge io opcode, or as an unimplemented operation.

	T ← sUnimplemented, GoTo[MiscTrap], At[MiscDisp1,15];	*WMDS Deimplemented

SetTime:	T ← Stack&-1, LoadPage[RS232Page], At[MiscDisp1,16];
	RTemp ← T, CallP[SetClrRS232];
	Skip[TimeOut];
	  Stack&+1 ← 0C, GoTo[MiscTail];
	Stack&+1 ← 100000C, GoTo[MiscTail];

OnPage[RS232Page];
SetClrRS232:
	RTemp1 ← IP[RSImage]C;
	T ← (SStkP&NStkP) xor (377C);
	StkP ← RTemp1, RTemp1 ← T, NoRegILockOK;
	T ← RTemp, Skip[R>=0];
	  Stack ← T ← (Stack) or T, Skip;
	  Stack ← T ← (Stack) and not T;
	StkP ← RTemp1, RS232 ← T, Return;

@SetDefaultPartition:
	T ← Stack&-1, LoadPage[XMiscPage], At[MiscDisp1,17];
	RTemp ← T, CallP[MXPar];
MiscPushT:	LU ← NextInst[IBuf];
	Stack&+1 ← T, NIRet;

@BitBLT:
	T ← Stack0, Opcode[365];
	AC2 ← T;
*Enter with StkP .eq. 2, Stack holding 2*scan-lines completed, and
*Stack0 in AC2 (a pointer to the BitBlt table)
	T ← MDShi;
	AC2hi ← T, LoadPage[bbPage];	*Long pointer to BitBLT table in AC2,AC2hi
	T ← (Cycle&PCXF) or (100000C), GoTo[bbBitBlt];

*StartIO is presently used only for Ethernet io which leaves a result in AC0
*(77777b if no Ethernet board, else host number); Mesa ignores the result
*and restores AC0.
@StartIO:
	T ← Stack&-1, LoadPage[eePage], Opcode[366];
	LU ← MNBR ← AC0, CallP[eeSIO];
	T ← MNBR;	*Unclobber AC0 (= Stack10 on 13 Jan 81)
	AC0 ← T, GoTo[P7Tail];

*Note: Stack[0:3] = task, Stack[4:17] = microaddress
*Start next opcode on even byte
@JRAM:	LU ← Cycle&PCXF, Skip[R Even], Opcode[367];
	  CSkipData;			*Can't cause refill
	Nop;
	LU ← APCTask&APC ← Stack&-1, Call[P7Ret];
	LU ← NextInst[IBuf], Call[P7Tailx];

@DST:	T ← NextData[IBuf], Opcode[370];
	T ← (LOCAL) + T, LoadPage[xfPage1];
	UseCTask, xfTemp ← T, CallP[SaveState];
	T ← (xfTemp) + (Add[MaxStack!,2]C), GoTo[portinz];	***???***

@LST:	T ← NextData[IBuf], Opcode[371];	
	xfTemp ← T, Call[SavePCInFrame];*NextData must be before SavePC call 
	T ← xfTemp, GoTo[LSTFgo];

@LSTF:	T ← RZero, Opcode[372];
	T ← NextData[IBuf], SALUF ← T;  *MB = 0  => free frame
LSTFgo:	T ← (LOCAL) + T, LoadPage[xfPage1];
	xfTemp ← T, GoToP[LoadState];	*xfTemp is pointer to saved state.

@WR:	T ← NextData[IBuf], Opcode[374];
	xfTemp ← T, LoadPage[xfPage1];
	Dispatch[xfTemp,16,2];
OnPage[xfPage1];
	T ← Stack&-1, Disp[.+1];
	GoTo[MiscTail], xfWDC ← T, DispTable[2,17,1];
	GoTo[MiscTail], xfXTSreg ← T;

@RR:	T ← NextData[IBuf], Opcode[375];
	xfTemp ← T, LoadPage[RRPage];
	Dispatch[xfTemp,15,3];
OnPage[RRPage];
	LoadPage[opPage3], Disp[.+1];
	GoToP[P7PushT], T ← xfWDC, DispTable[6,17,1];
	GoToP[P7PushT], T ← xfXTSreg;
	GoToP[P7PushT], T ← xfXTPreg;
	GoToP[P7PushT], T ← xfATPreg;
	GoToP[P7PushT], T ← xfOTPreg;
	GoToP[P7PushT], T ← MDShi;

@BRK:	T ← Zero, GoTo[kfcr], Opcode[376];

*Cause pagefault trap--done only by fault, not supposed to be encountered in
*instruction stream.
TrapFlap:	T ← (PCFReg) - 1, Opcode[377];	*back up PCF by one
	RTemp ← T, LoadPage[0];
	PCF ← RTemp, GoToP[StartMemTrap];

*Unused opcodes on page 7
	T ← sUnimplemented, GoTo[kfcr], Opcode[373];

:END[MesaX];