*-----------------------------------------------------------
Title[DMesaDefs.mc...December 12, 1985  10:27 AM...Willie-Sue];
*-----------------------------------------------------------

*-----------------------------------------------------------
* Assembly options
*-----------------------------------------------------------
* Compile the Alto-Mesa emulator unless AltoMode is previously set to 0.
IfDef[AltoMode, , Set[AltoMode, 177777]];

* nEntryPoints may be either 1 or 3 in Alto mode, only 1 in PrincOps mode.
* Note that 1 entry point => restart opcode after page fault.
IfDef[nEntryPoints, , Set[nEntryPoints, 1]];

*-----------------------------------------------------------
* RM registers
*-----------------------------------------------------------

SetRMRegion[RMforIFU];	*RM region 0
:If[AltoMode];		********** Alto version **********
	RVN[DLink];		* Xfer destination link
	RVN[SLink];		* Xfer source link
	RVN[ATPReg];		* Allocation trap parameter
	RVN[OTPReg];		* Other trap parameter
	RVN[Sticky];		* Sticky flags for floating point
:Else;			******** PrincOps version ********
	Reserve[1];		* NWW: defined in RegisterDefs.mc
	RVN[CurrentPSB];	* PDA-relative address of current PSB
	RVN[CurrentTime];	* Current process time, in ~50 ms ticks
	RVN[XferFlags];		* Xfer control and state flags
	RVN[TrapParam];		* Xfer trap parameter
:EndIf;			**********************************
	RVN[XTSReg];		* Xfer trap state
	RVN[WDC];		* Wakeup disable counter
	RVN[MDSHi];		* Main data space -- high part
*	Reserve[1];		* An unused register -- wow!
	RVN[RTempX];		* Not any more!
	RVN[RTemp0];		* General temporaries
	RVN[RTemp1];
	RVN[RTemp2];
	RVN[RTemp3];
	RVN[RTemp4];
	RVN[RTemp5];		* RVRel 16 and 17 must be temps, for
	RVN[RTemp6];		*  multiply and divide subroutines

:If[Not[AltoMode]];	******** PrincOps version ********
SetRMRegion[AEmRegs];	* RM region 1 (overlay Alto Emulator registers)
	Reserve[1];		* Skip over R400
	RVN[TickCount];		* Divides down 17-ms interrupts to make ticks
	RVN[Sticky];		* Sticky flags for floating point
	RVN[MaintPanel];	* Maintenance panel code
:EndIf;			**********************************

* RM registers (cont'd)

* Special uses of the Mesa RM registers:

:If[AltoMode];		********** Alto version **********
	RME[PDAHi, MDSHi];	* PDA is the same as MDS at present
	RME[XferFlags, RTemp6];	* Xfer control flags

* XferFlags bit assignments.
	MC[xf.trap, 0];		* Not used in Alto mode
	MC[xf.push, 0];		* Not used in Alto mode
	MC[xf.free, 1];		* Free local frame

:Else;			******** PrincOps version ********
* Temporary register assignments, used only inside Xfer and when calling Xfer.
	RME[DLink, RTemp5];	* Xfer destination link
	RME[SLink, RTemp6];	* Xfer source link

* Temporary register assignments, for passing parameters thru fault handler.
* FaultParam0 and FaultParam1 must be preserved across Requeue.
	RME[FaultParam0, TrapParam]; * First or low-order fault parameter
	RME[FaultParam1, RTemp3]; * Second or high-order fault parameter

* XferFlags bit assignments.
* Note: xf.invalidContext must have the appropriate value (usually 0) any
* time a fault or trap may occur.  Other flags are relevant only inside Xfer.
* The low 3 bits are dispatched upon inside Xfer, so be circumspect about
* reassigning them.
	MC[xf.invalidContext, 100000]; * Current context is invalid
	MC[xf.trap, 4];		* Store TrapParam in destination frame
	MC[xf.push, 2];		* Push SLink and DLink onto stack
	MC[xf.free, 1];		* Free local frame
:EndIf;			**********************************

* 16 and 17 must be temporaries (for MulSub and DivSub)
	RM[MulDivArg, Or[!RMforIFU, 17]];

*-----------------------------------------------------------
* Base registers
*-----------------------------------------------------------

* BRs 0-3 are addressable as MemBX-relative registers.
* Of these, 0 and 1 are used as MemBX-relative registers by Mesa,
* thereby consuming registers 4, 5, 10, 11, 14, 15 also.
* The other registers in [0..17] are used as ordinary registers
* and should not be addressed from the IFU.
	BRX[L, 0];		* {mds, L} Local frame, = G xor 1
	BRX[G, 1];		* {mds, G} Global frame, = L xor 1

	BR[SD, 2];		* {mds, SD} System Dispatch table

* BRs 34-37 are addressable from the IFU.
* 36 and 37 are permanently assigned in ADefs.mc (MDS and CODE).
* 34 and 35 are also used in DMesaProcess.mc.
	BR[LPtr, 34];		* Temp for Long Pointer instructions

:If[AltoMode];		********** Alto version **********
	BR[PDA, IP[MDS]];	* PDA is the same as MDS at present
:Else;			******** PrincOps version ********
	BR[PDA, 3];		* Base of Process Data Area
:EndIf;			**********************************
	BR[MapBitsBR, 25];

*-----------------------------------------------------------
* System constants
*-----------------------------------------------------------

	MC[AV, 1000];
	Set[SDLoc, 1100];
	MC[GFT, 1400];

* SD indices for Mesa traps
	MC[sBreak, 0];
	MC[sStackError, 2];
	MC[sWakeupError, 3];
	MC[sXferTrap, 4];
	MC[sUnimplemented, 5];
	MC[sControlFault, 7];
	MC[sSwapTrap, 10];
	MC[sUnbound, 13];
	MC[sZeroDivisor, 14];
	MC[sDivideCheck, 15];
	MC[sHardwareError, 16];
	MC[sProcessTrap, 17];
	MC[sBoundsFault, 20];
	MC[sPointerFault, 21];
	MC[sBoot, 276];

:If[AltoMode];		********** Alto version **********
* SD indices for Mesa faults (handled as traps in Alto Mesa and
* pre-Rubicon Pilot Mesa.
	MC[sAllocListEmpty, 6];
	MC[sPageFault, 11];
	MC[sWriteProtect, 12];
:Else;			******** PrincOps version ********
* Fault queue offsets (2 * corresponding PrincOps FaultQueueIndex)
	MC[qFrameFault, 0];
	MC[qPageFault, 2];
	MC[qWriteProtectFault, 4];
:EndIf;			**********************************

* Miscellaneous definitions
:If[AltoMode];		********** Alto version **********
	MC[MesaStopLoc, 26];	* Communication with the Nova World
	MC[CurrentState, 23];
:Else;			******** PrincOps version ********
	MC[PDAhi, 1];		* PDA starts at VM 200000
	MC[pilotMDSHi, 76];	* MDS initially starts at VM 17400000
:EndIf;			**********************************

* Mesa instruction set number
	Set[MesaInsSet, IfE[AltoMode, 0, 1, 2]];
	InsSet[MesaInsSet, nEntryPoints];

* Stack size (size of StateVector.stk array)
	Set[sizeStack, IfE[AltoMode, 0, 16, 10]];

*-----------------------------------------------------------
* Mesa opcode definitions
*-----------------------------------------------------------

Set[MOpcodeVal, 0];
M[MOp, (IfSE[#1, , UndefOp[MOpcodeVal], Set[MOp#1, MOpcodeVal]]
	Set[MOpcodeVal, Add[MOpcodeVal, 1]])];
M[MesaOps, (MOp[#1] MOp[#2] MOp[#3] MOp[#4] MOp[#5] MOp[#6] MOp[#7] MOp[#8])];
M[UndefOp, IFUPause[#1, 1, L, 0, UnimplOpcodeTrap, 17, 0, 0]];

*       xx0    xx1    xx2    xx3    xx4    xx5    xx6    xx7

MesaOps[NOOP,  ME,    MRE,   MXW,   MXD,   NOTIFY,BCAST, REQUEUE];	* 00x
MesaOps[LL0,   LL1,   LL2,   LL3,   LL4,   LL5,   LL6,   LL7];		* 01x
MesaOps[LLB,   LLDB,  SL0,   SL1,   SL2,   SL3,   SL4,   SL5];		* 02x
MesaOps[SL6,   SL7,   SLB,   PL0,   PL1,   PL2,   PL3,   LG0];		* 03x
MesaOps[LG1,   LG2,   LG3,   LG4,   LG5,   LG6,   LG7,   LGB];		* 04x
MesaOps[LGDB,  SG0,   SG1,   SG2,   SG3,   SGB,   LI0,   LI1];		* 05x
MesaOps[LI2,   LI3,   LI4,   LI5,   LI6,   LIN1,  LINI,  LIB];		* 06x
MesaOps[LIW,   LINB,  LADRB, GADRB, LCO,    ,     ASSIGNREF,ASSIGNREFNEW]; * 07x

MesaOps[R0,    R1,    R2,    R3,    R4,    RB,    W0,    W1];		* 10x
MesaOps[W2,    WB,    RF,    WF,    RDB,   RD0,   WDB,   WD0];		* 11x
MesaOps[RSTR,  WSTR,  RXLP,  WXLP,  RILP,  RIGP,  WILP,  RIL0];		* 12x
MesaOps[WS0,   WSB,   WSF,   WSDB,  RFC,   RFS,   WFS,   RBL];		* 13x
MesaOps[WBL,   RDBL,  WDBL,  RXLPL, WXLPL, RXGPL, WXGPL, RILPL];	* 14x
MesaOps[WILPL, RIGPL, WIGPL, RSTRL, WSTRL, RFL,   WFL,   RFSL];		* 15x
MesaOps[WFSL,  LP,    SLDB,  SGDB,  PUSH,  POP,   EXCH,  LINKB];	* 16x
MesaOps[DUP,   NILCK, NILCKL,BNDCK,  ,      ,      ,      ];		* 17x

MesaOps[J2,    J3,    J4,    J5,    J6,    J7,    J8,    J9];		* 20x
MesaOps[JB,    JW,    JEQ2,  JEQ3,  JEQ4,  JEQ5,  JEQ6,  JEQ7];		* 21x
MesaOps[JEQ8,  JEQ9,  JEQB,  JNE2,  JNE3,  JNE4,  JNE5,  JNE6];		* 22x
MesaOps[JNE7,  JNE8,  JNE9,  JNEB,  JLB,   JGEB,  JGB,   JLEB];		* 23x
MesaOps[JULB,  JUGEB, JUGB,  JULEB, JZEQB, JZNEB, JIB,   JIW];		* 24x
MesaOps[ADD,   SUB,   MUL,   DBL,   DIV,   LDIV,  NEG,   INC];		* 25x
MesaOps[AND,   OR,    XOR,   SHIFT, DADD,  DSUB,  DCOMP, DUCOMP];	* 26x
MesaOps[ADD01,  ,      ,      ,      ,      ,      ,      ];		* 27x

MesaOps[EFC0,  EFC1,  EFC2,  EFC3,  EFC4,  EFC5,  EFC6,  EFC7];		* 30x
MesaOps[EFC8,  EFC9,  EFC10, EFC11, EFC12, EFC13, EFC14, EFC15];	* 31x
MesaOps[EFCB,  LFC1,  LFC2,  LFC3,  LFC4,  LFC5,  LFC6,  LFC7];		* 32x
MesaOps[LFC8,  LFC9,  LFC10, LFC11, LFC12, LFC13, LFC14, LFC15];	* 33x
MesaOps[LFC16, LFCB,  SFC,   RET,   LLKB,  PORTO, PORTI, KFCB];		* 34x
MesaOps[DESCB, DESCBS,BLT,   BLTL,  BLTC,   ,     ALLOC, FREE];		* 35x
MesaOps[IWDC,  DWDC,  STOP,  CATCH, MISC,  BITBLT,STARTIO, ];		* 36x
MesaOps[DST,   LST,   LSTF,   ,     WR,    RR,    BRK,    ];		* 37x

*-----------------------------------------------------------
* IFU entry point macros
*-----------------------------------------------------------
* Call(s) should appear IMMEDIATELY BEFORE the entry vector.
* Each call defines a label "@opcode" at the current IM location, and
* forces the next nEntryPoints instructions to comprise an IFU entry vector.

* Note: due to MicroD symbol table overflow problems, a label "@opcode"
* is defined only for the first opcode in a group of consecutive declarations.

* IFUR[opcode, length, memBase, options];	Regular opcode
* IFUP[opcode, length, memBase, options];	Pause opcode
* IFUJ[opcode, length, memBase, options];	Jump opcode

* opcode = one of the opcode names defined above
* length = 1, 2, or 3
* memBase = defined MemBase name

* Options (zero or more, in any order):
* N[n]		n = 0 to 16 or "noN"
* SignExtend
* PackedAlpha
* RBase[rBase]	rBase = MesaRegs or AEmRegs (Alto mode only -- not PrincOps)
* Disp[n]	n = -40 to 37 (displacement for 1-byte jumps)

M[IFUR, IOpLabel[#1] (IOp#4, IOp#5, IOp#6, IOp#7, IFUDeflt)
  IFUReg[MOp#1, #2, #3, RShift[CRB@, 4], ILC, IValN, IValSign, IValPA]];
M[IFUP, IOpLabel[#1] (IOp#4, IOp#5, IOp#6, IOp#7, IFUDeflt)
  IFUPause[MOp#1, #2, #3, RShift[CRB@, 4], ILC, IValN, IValSign, IValPA]];
M[IFUJ, IOpLabel[#1] (IOp#4, IOp#5, IOp#6, IOp#7, IFUDeflt)
  IFUJmp[MOp#1, #2, #3, RShift[CRB@, 4], ILC, IValSign]];

M[IOp, ];
M[IOpN, Set[IValN, #1]];
M[IOpSignExtend, Set[IValSign, 1]];
M[IOpPackedAlpha, Set[IValPA, 1]];
M[IOpDisp, Set[IValSign, #1]];
:If[AltoMode];		********** Alto version **********
Equate[IOpRBase, KnowRBase];
:EndIf;			**********************************

M[IFUDeflt, TopLevel[] KnowRBase[RMforIFU]
  Set[IValN, 17] Set[IValSign, 0] Set[IValPA, 0]];

Set[LastILC, 177777];
M[IOpLabel, IfE[IP[ILC], LastILC, , @#1: Set[LastILC, IP[ILC]]]];

*-----------------------------------------------------------
* IFU exit macros and top-of-stack conventions
*-----------------------------------------------------------

*	[0]: TOS = Stack[StkP], TOS-1 = Stack[StkP-1]
*	[1]: TOS = MD, TOS-1 = T & Stack[StkP-1]
*	[2]: TOS = T & Stack[StkP+1], TOS-1 = Stack[StkP]

* State 0 is the canonical form, with all values stored in the hardware stack.
* It is the only form if a single entry point is being used.

* IFUNextN = IFUJump[N] if 3 entry points are being used.

* If only 1 entry point, IFUNext0 or IFUNext0CF is the normal exit (IFUNext0CF
* checks for faults first).  IFUNext1 branches to code that puts MD on the
* stack and exits.  IFUNext2 is ordinarily illegal, but can be used with the
* special "StackT" source and destination:
*	StackT← (StackT)+T, IFUNext2;
* is equivalent to:
*	Stack&-1← T← (Stack&-1)+T, IFUJump[2]; * if 3 entry points, but
*	Stack← (Stack)+T, IFUJump[0];	* if 1 entry point.

Set[multEntryPoints, IfE[nEntryPoints, 1, 0, 177777]];
M[IfMEP, If[multEntryPoints]];
M[If1EP, If[Not[multEntryPoints]]];

:IfMEP;
M[IFUNext0, IFUJump[0]];
M[IFUNext1, IFUJump[1]];
M[IFUNext2, IFUJump[2]];
M[IFUNext0CF, IFUJump[0]];
M[StackT←, Stack&-1←T←]; Equate[StackT, Stack&-1];
:Else;
M[IFUNext0, IFUJump[0]];
M[IFUNext1, Branch[PushMD]];
M[IFUNext2, IFUJump[0]];
M[IFUNext0CF, Branch[CheckFault0]];
Equate[StackT←, Stack←]; Equate[StackT, Stack];
:EndIf;


*-----------------------------------------------------------
* MISC opcode entry definition
*-----------------------------------------------------------
* MiscTable[n] places the current instruction at the entry point for
* MISC operation n.

Set[MT0Loc, 4000];	* Base for 000-077 dispatch
Set[MT1Loc, 4400];	* Base for 100-177 dispatch
Set[MT2Loc, 6000];	* Base for 200-277 dispatch
Set[MT3Loc, 6400];	* Base for 300-377 dispatch

M[MiscTable,
  At[Select[RShift[#1, 6], MT0Loc, MT1Loc, MT2Loc, MT3Loc],
    Add[LShift[And[#1, 77], 2], 1]]];

:If[AltoMode];		********** Alto version **********
M[MiscOpcodeUnimplemented,
  (MiscTable[#1], T← sUnimplemented, StkP-1, Branch[SavePCAndTrap])];
:Else;			******** PrincOps version ********
M[MiscOpcodeUnimplemented,
  (MiscTable[#1], Branch[UnimplOpcodeTrap])];
:EndIf;			**********************************

% Dorado Alto-Mesa microcode
Note: most of these conventions currently apply to Pilot Mesa as well,
though the PrincOps says otherwise!

This code is strictly for Mesa 6
	AV=1000C
	SD=1100C
	GFT=1400C

State Block Configuration (Alto Mesa)
	alpha		Stack[1]
	 ...
	alpha+7		Stack[8]
	alpha+10	brkbyte,,skp
	alpha+11	mx (dest)
	alpha+12	my (source)

Local frame
	L	-> global frame
	L+1	PC (Alto: if PC odd then -(PC/2) else PC/2)
	L+2	-> caller's frame
	L+3	Alto: unused; PrincOps: place to store trap parameter
	L+4	local 0
	L+5	...

Global frame configuration
	G-3	...
	G-2	external link 1
	G-1	external link 0
	G	GFI,,code links(1 bit) [code links=0 => links are in 
				the frame, =1 => in the code segment]
	G+1	code base low
	G+2	code base high (Alto XMesa or PrincOps)
	G+3	global 0
	G+4	...

Code segment
	C-3	...
	C-2	external link 1
	C-1	external link 0
	CP	reserved
	CP+1	reserved
	...
	CP+2n+2	word pc offset (n = procedure number, as in LFCn)
	CP+2n+3	frame size index (in lower byte)
	...
%

%
*-----------------------------------------------------------
Alto-Mesa notes:
*-----------------------------------------------------------

Alto-Mesa differs from PrincOps in the following systematic ways:

1. The byte order of code is backwards (right=even, left=odd).
This is true ONLY of code, not of arbitrary byte arrays (e.g., jump tables).

2. All 3-byte instructions are aligned.  This means that if the opcode
is an even byte, the odd byte is ignored and alpha,,beta is taken from
the next full word.  (Note the byte order of alpha,,beta!)
A few 1-byte instructions are also aligned.  This means that if the opcode
is an even byte, the odd byte is ignored and the next opcode is taken from
the even byte of the next word.

3. Jump displacements are measured from the last byte of the instruction,
not from the opcode.

4. Frame displacements are handled inconsistently.  Local 0 is word 4
of the local frame.  In "Byte" instructions (e.g., LLB), the operand byte
already includes the offset, but in "N" and "Pair" instructions it does
not.  That is, the following instructions refer to the same item (local 0):
	LL0
	LLB 4
	RILP <0,,x>

(n.b. at present, Pilot follows this convention also.)

5. Alto-Mesa imposes "minimal stack" requirements in certain instructions.
However, this Mesa implementation requires minimal stack only in the
process/monitor opcodes.
%