BUILTIN[ER, 22]; ER[D1Lang.Mc...19-Jun-82, 0];
* Modified by Taft, June 19, 1982  2:53 PM -- add StackNoUfl←
* Modified by McDaniel, 18Sept81--Fix Data macro -- avoid placement errs
* Modified by Taft 14-Aug-81--Data macro accepts 9-bit values in all 4 fields.
* Modified by Fiala 11 Nov 80--additional shifter macro error checks

BUILTIN[MACRO,2];	*Declare macro
BUILTIN[NEUTRAL,3];	*Declare neutral
BUILTIN[MEMORY,4];	*Declare Memory[name,wordsize,length,srcmacro,
			*sinkmacro,tagmacro,postmacro]
BUILTIN[TARGET,5];
BUILTIN[DEFAULT,6];
BUILTIN[FIELD,7];	*Declare field[1stbit,lastbit]
BUILTIN[PF,10];		*Preassign value to field
BUILTIN[SET,11];	*Declare integer and set value
BUILTIN[ADD,12];	*Add up to 8 integers
BUILTIN[IP,13];		*Integer part of address
BUILTIN[IFSE,14];	*If string #1 .eq. string #2 then #3, else #4
BUILTIN[IFA,15];	*If any bits of field #1 assigned then #2, else #3
BUILTIN[IFE,16];	*If integer #1 .eq. integer #2 then #3, else #4
BUILTIN[IFG,17];	*If integer #1 .gr. integer #2
BUILTIN[IFDEF,20];	*If string #1 in symbol table and not unbound
			*address then #2, else #3
BUILTIN[IFME,21];	*If memory part of address #1 .eq. string #2 then
			*#3, else #4
*BUILTIN[ER,22];	*Error message (ER[string,abortcode,int])
			*abortcode = 0 message, 1 fatal, 2 error, 3 warning
BUILTIN[LIST,23];	*Set listing mode for memory
*BUILTIN[INSERT,24];	*Insert file
BUILTIN[NOT,25];	*1's complement
BUILTIN[REPEAT,26];	*Repeat the text #2 #1 times
BUILTIN[OR,27];		*Inclusive OR up to 8 integers
BUILTIN[XOR,30];	*Exclusive OR up to 8 integers
BUILTIN[AND,31];	*AND up to 8 integers
BUILTIN[COMCHAR,32];	*Set comment char for conditional assembies
*BUILTIN[BITTABLE,33];	*Makes #1 a bit table of length #2 bits
*BUILTIN[GETBIT,34];	*Is the bit in bittable #1 at pos. #2
*BUILTIN[SETBIT,35];	*SETBIT[table,bit1,nbits,distance,val]
*BUILTIN[FINDBIT,36];	*FINDBIT[table,bit1,nbits,distance,hopdist,nhops]
*BUILTIN[MEMBT,37];	*MEMBT[memory table] creates a bit table for memory
BUILTIN[LSHIFT,40];	*Shifts the integer #1 left #2 positions
BUILTIN[RSHIFT,41];	*Shifts the integer #1 right #2 positions
BUILTIN[FVAL,42];	*FVAL[field] is an integer whose value is the
			*current contents of the field
BUILTIN[SELECT,43];	*#1 is an integer .ge. 0 and .le. 7.  Evaluates
			*#2 IF #1 = 0, ..., #9 if #1 = 7.  Error if #1 > 7
BUILTIN[SETPOST,44];	*Set post-evaluation macro (SETPOST[mem,macro])
BUILTIN[LISTFIELDS,46];	*LISTFIELDS[mem,word] assembles word as for DEFAULT
			*and the 1-bits denote the right-most bits of
			*fields in the octal listing.
BUILTIN[SETMBEXT,47];	*Set .MB file extension
BUILTIN[SUB,50];	*SUB[a1,a2,...,an] = a1-a2-...-an (16-bit args)
BUILTIN[EQUATE,51];	*EQUATE[new,old] gives new same definition as old
BUILTIN[ASMMODE,52];	*ASMMODE[0] is normal, ASMMODE[1] ignores all
			*statements except those beginning with ":"
BUILTIN[TRACEMODE,53];	*TRACEMODE[n,v] turns on tracing feature n if v ne 0,
			*off if v=0.  n = 0 is trace symbol insertions,
			*1 is trace all applications of the form name[args]
BUILTIN[WHILE,54];	*WHILE[expr, stat] repeatedly executes stat while expr
			*is nonzero

BUILTIN[M,2];		*=MACRO (internal use)
BUILTIN[N@,3];		*=NEUTRAL
BUILTIN[F@,7];		*=FIELD
BUILTIN[EQ@,51];	*=EQUATE

SETMBEXT[DIB];

COMCHAR[~];		*Makes "*~" work like "%" at beginning of lines

%Micro runs faster when tokens used in macros are defined before the macro
definition, and the arrangment of the stuff in this file is partially the
result of this consideration.
%

*Allow conditional assemblies with :IF's nested to 4 levels
SET[ALEV@,0];	*No. nested IF's
SET[ASMF@,1];	*1 if assembling, 0 if not assembling
SET[ASML@,1];	*1 if assembling at this level, 0 if ignoring
SET[L1@,0]; SET[L2@,0]; SET[L3@,0]; SET[G1@,0]; SET[G2@,0]; SET[G3@,0];

M[IF,SELECT[ALEV@,,SET[L1@,ASML@] SET[G1@,ASMF@],
    SET[L2@,ASML@] SET[G2@,ASMF@],	SET[L3@,ASML@] SET[G3@,ASMF@],
    ER[:IF's.nested.more.than.4.levels,1]]
  SET[ALEV@,ADD[ALEV@,1]] SET[ASML@,ASMF@]
  IFE[ASML@,1,
    IFE[#1,0,ASMMODE[1] SET[ASMF@,0],ASMMODE[0] SET[ASMF@,1]]]];

M[NOIF@,ER[No.:IF.preceding.:#1,1]];
M[ELSEIF,IFE[ALEV@,0,NOIF@[ELSEIF],
  IFE[ASML@,1,IFE[ASMF@,1,SET[ASMF@,0] SET[ASML@,0] ASMMODE[1],
    SET[ASMF@,#1] ASMMODE[IFE[ASMF@,0,1,0]]]]]];

M[ELSE,IFE[ALEV@,0,NOIF@[ELSE],
  IFE[ASML@,1,IFE[ASMF@,1,SET[ASMF@,0] SET[ASML@,0] ASMMODE[1],
    ASMMODE[0] SET[ASMF@,1]]]]];

M[ENDIF,SELECT[ALEV@,NOIF@[ENDIF],
    SET[ASMF@,1] SET[ASML@,1],		SET[ASML@,L1@] SET[ASMF@,G1@],
    SET[ASML@,L2@] SET[ASMF@,G2@],	SET[ASML@,L3@] SET[ASMF@,G3@]]
  SET[ALEV@,SUB[ALEV@,1]] IFE[ASMF@,1,ASMMODE[0]]];

*IM field definitions in arrangement expected by MicroD
F@[RSTK,0,3];		*RM address, STKP modification
  F@[RSTK13,1,3];	*Three low bits (for IM←)
  F@[RSTK23,2,3];	*Two low bits (for READIM)
F@[ALUF,4,7];		*ALU function select (address in ALUFM)
F@[BSEL,10,12];		*Source for B
  F@[BSEL0,10,10];	*High bit of BSEL (indicates constant selected)
F@[LC,13,15];		*Controls source and load of R and T
F@[ASEL,16,20];		*A op select
  F@[ASEL0,16,16];
F@[BLK,21,21];		*Block task (non-emulator) -or- stack op (emulator)
F@[FF,22,31];		*Function
  F@[FA,22,23];		*FF[0:1] used with mem ops
  F@[F1,22,25];		*FF[0:3] used with constants and FF shifts
  F@[F2,26,31];		*FF[4:7] "
  F@[FBC,24,31];	*FF[2:7] used for FF < 100 decodes
F@[JCN,32,41];		*Jump control
F@[BRKP,42,43];		*PE16 and PE17 both 0 (no brkp) or both 1 (brkp)

%Dispatch table stuff isn't ready yet.
F@[DTAB@,44,57];	*Dispatch table applicable to this instruction

*60:63 unused
F@[BEONES@,64,77];	*Additional bits in placement that must be 1's

Interim kludges:
%
F@[GPW0@,61,77];
F@[W0@,61,61];
F@[GLB@,62,62];
*63=1 tells MicroD that 64:71 are the page for mi placement

F@[RETCL@,100,101];	*2 = does a RETURN, CORETURN, or IFUJUMP
			*1 = does a CALL or CORETURN
F@[JBC@,102,102];	*Has a branch condition in JCN
F@[UFF@,103,103];	*FF field unavailable for long GoTo or long Call
  F@[JUFF@,102,103];	*Combination of JBC@ and UFF@ fields
F@[W1@,104,117];	*Imaginary address of unconditional or false branch

F@[BRGO@,120,121];	*2 = branches
			*1 = goes
F@[EMU@,122,122];	*Print as emulator instruction
F@[COND@,123,123];	*Has a branch condition
F@[W2@,124,137];	*Imaginary address of conditional branch when true


*Fields for IFUM assembly
F@[PA@,0,0];		*Packed alpha (shifted to bit 5 by MicroD)
F@[NENT@,1,2];		*No. instructions in entry vectors-1
F@[IFD@,4,17];		*IM address high-true
			*(transformed by MicroD, inverted, and put in 6:17)
F@[SGN@,20,20];		*Sign
*Three parity bits filled in by Midas
F@[LEN'@,24,25];	*Length' (1, 2, or 3 bytes)
F@[RBASEB'@,26,26];	*RBase
F@[MEMB@,27,31];	*MemBase init
F@[TYPE'@,32,33];	*Pause', jump'
F@[OP@,34,37];		*N


*Fields for IMMASK assembly
F@[CONMSK@,0,17];	*Constraint mask: bit n = 1 => can place at n mod 20
F@[DTLEN@,20,23];	*Dispatch table length minus 1


F@[WRD0@,0,17]; F@[WRD1@,20,37];

*The ? neutral is used with expressions not intended for connection
*to other expressions.
N@[?];

%The various sources and destinations connected by "←" reduce to the
following source and destination classes:
%
N@[RB];	*Feed A, B, or shifter
N@[T];	*Feed A or B
N@[MD];	*Feed R, T, B, or A
N@[B];	*B
N@[XB];	*Slow B
N@[A];	*A
N@[Q];	*Feeds B (BSEL) or A (FF64, FETCH←, or STORE←)
N@[ID];	*A, FETCH←, or STORE←
N@[PD];	*ALU ops, INPUT function, or ALUFM read
N@[S@];	*Small constants

*Destinations expecting small constant as source (also RBASE←B, MEMBASE←B,
*CNT←B, MEMBASE←BRaddr, MEMBASE←BRXaddr, and MEMBASEX←BRXaddr)
N@[RBASE←]; N@[CNT←]; N@[MEMBASEX←]; N@[MEMBASE←]; N@[MEMBX←];

N@[RB←];	N@[T←];		N@[B←];		N@[PD←];	N@[A←];
N@[FETCH←];	N@[STORE←];	N@[MM←];	N@[BR@];	N@[BRX@];

*Connection macros
M[B←B,IFA[BSEL,B,BSEL[1]B]];	M[B←XB,IFA[BSEL,XB,BSEL[1]XB]];
M[MAPBUF←,B←];			M[DBUF←,B←];
M[A←A,A];			M[PD←PD,PD];


*Define integers here before they are used for faster assembly
SET[Z1@,0];  SET[Z2@,0];  SET[SC@,0];  SET[RLAST@,0];  SET[ONP@,0];
SET[T1@,0];  SET[T2@,0];  SET[T3@,0];  SET[TS@,1];     SET[CRB@,0];

SET[XTASK,0];		*Task for which instructions are being assembled
			*(affects STK stuff, references)

M[NEARGS@,ER[Not.enough.args.for.#1,2]];
M[TMARGS@,ER[Too.many.args.for.#1,2]];
M[FFT@,ER[FF.used.twice,2]];
M[FAT@,ER[FA.used.twice,2]];
M[IMPB@,ER[Impossible.B←,2]];

M[SOK@,IFE[TS@,1,ER[#1.illegal.in.subroutine,2]]];
M[TLOK@,IFE[TS@,2,ER[#1.illegal.at.top.level,2]]];
M[ILLIOF@,IFE[XTASK,0,EMU@[1],ER[#1.allowed.only.in.task.0,2]]];
M[ILLE@,IFE[XTASK,0,ER[#1.ill.in.emu,2]]];
M[ILLIO@,IFE[XTASK,0,EMU@[1],IFE[XTASK,17,EMU@[1],ER[#1.ill.in.io.task,2]]]];
M[ILLEF@,IFE[XTASK,0,ER[#1.ill.in.emu,2],IFE[XTASK,17,ER[#1.ill.in.flt,2]]]];

M[FF64,IFA[FBC,FFT@[],IFA[COND@,JUFF@[3],UFF@[1]]FBC[#1]]];
M[FF256,IFA[FF,FFT@[],IFA[COND@,JUFF@[3],UFF@[1]]FF[#1]]];

*The following macros define B destinations encodable as either
*FF64's or, if FF encodes an external B source, in BSEL.
*#1 is the value for FF, #2 for BSEL
M[FFBSL1@,IFG[FVAL[FF],177,IMPB@[],IFG[FVAL[FF],157,BSEL[#1],IMPB@[]]]];
M[FFBSEL@,IFA[FBC,IFE[FVAL[ASEL0],1,FFBSL1@[#2],IMPB@[]],FF64[#1]]];
*M[FFBSEL256@,IFA[FF,IFE[FVAL[ASEL0],1,FFBSL1@[#2],IMPB@[]],FF256[#1]]];

*Source and sink macros invoked when address symbols in the text appear
*as sources or destinations in "←" clauses.

**Macros for real RM addresses
M[RSA@,IFA[RSTK,IFE[FVAL[RSTK],Z2@,,FF64[ADD[40,Z2@]]],RSTK[Z2@]]];
M[RSINK@,(SET[Z1@,IP[#1]] SET[Z2@,AND[Z1@,17]]
  IFE[AND[360,Z1@],CRB@,
    IFG[XTASK,0,RSA@,IFE[FVAL[BLK],1,FF64[ADD[40,Z2@]],BLK[0] RSA@]],
    RSTK[Z2@] FF256[ADD[220,RSHIFT[Z1@,4]]]
  ])
RB←];

*Cleverly generate "value-won't-fit" error on read outside region
M[RSRC@,RSTK[XOR[CRB@,IP[#1]]] IFE[XTASK,0,BLK[0]] RB];

**Macros for RBASE-relative addresses
M[RDSRC@,RSTK[#1]IFE[XTASK,0,BLK[0]]RB];
M[RDSINK@,IFA[RSTK,
  IFE[FVAL[RSTK],IP[#1],,FF64[ADD[40,IP[#1]]]],RSTK[#1]]RB←];

M[W@,];				*Dummy macro required for memory def.
M[TSRC@,IP[#1]C];		*Make constant from TASKN address
M[DVSRC@,LSHIFT[IP[#1],10]C];	*Make constant from DEVICE address
M[BRSRC@,SET[SC@,IP[#1]]BR@];	*Make small constant for MemBase←
M[BRXSRC@,SET[SC@,IP[#1]]BRX@];	*Make small constant for MemBaseX←

%Memory names and sizes must agree with those in Midas, except that IM and
IFUM must agree with the form expected by MicroD.  Also, MicroD consumes
VERSION, RVREL, IMLOCK, and IMMASK, which are not passed through to Midas.
%
MEMORY[IM,140,10000,W@,W@];
MEMORY[RM,20,400,RSRC@,RSINK@];
MEMORY[IFUM,40,2000,W@,W@];
MEMORY[ALUFM,10,20,W@,W@];
MEMORY[STK,20,400,W@,W@];
MEMORY[BR,40,40,BRSRC@,W@];	*Fake to show MemBase contents symbolically
MEMORY[BRX,40,4,BRXSRC@,W@];	*Fake for MemBX-relative addressing
MEMORY[DEVICE,20,400,DVSRC@,W@]; *Fake to show TIOA contents symbolically
MEMORY[TASKN,20,20,TSRC@,W@];	*Fake to show tasks symbolically
MEMORY[VERSION,20,1,W@,W@];	*Fake to tell MicroD this is Dorado model 1
MEMORY[RVREL,0,20,RDSRC@,RDSINK@]; *Fake memory for RM stuff
MEMORY[IMLOCK,1,10000,W@,W@];	*Fake memory for MicroD word reservations
*MEMORY[DISP,40,10000,W@,W@];	*MicroD dispatch table info (unimplemented)
MEMORY[IMMASK,24,10000,W@,W@];	*Fake memory for IM placement constraints

%2nd arg of LIST controls output as follows:
1 = (TAG) nnnn nnnn nnnn ...
2 = (TAG) F1←3, F2←4, ...
4 = numerically-ordered list of address symbols
10 = alphabetically-ordered list of address symbols
20 = (TAG) 1nnnnn 1nnnnn ... (16-bit printout iff 1 set also)
LISTFIELDS overrules the 1 and 20 numeric printout modes
%
LISTFIELDS[IM,RSTK[1] ALUF[1] BSEL[1] LC[1] ASEL[1] BLK[1] FF[1] JCN[1]
*  DTAB@[1] BEONES@[1]
  GPW0@[1]
  RETCL@[1] JBC@[1] UFF@[1] W1@[1]
  BRGO@[1] EMU@[1] COND@[1] W2@[1] ];
LISTFIELDS[IFUM,PA@[1] NENT@[1] IFD@[1] SGN@[1] LEN'@[1] RBASEB'@[1] MEMB@[1]
  TYPE'@[1] OP@[1] ];
LISTFIELDS[IMMASK,CONMSK@[1] DTLEN@[1]];
LIST[IM,25]; LIST[RM,25]; LIST[IFUM,21]; LIST[ALUFM,21];
LIST[BR,4]; LIST[BRX,4]; LIST[DEVICE,4]; LIST[TASKN,4]; LIST[IMMASK,21];
LIST[VERSION,0]; LIST[IMLOCK,0]; LIST[RVREL,4]; LIST[,25]; *LIST[DISP,0];

IM[ILC,0];		*Location counter for IM
*DISP[DLC,0];		*Location counter for DISP
IMMASK[MASKLC@, 0]	*Location counter for IMMASK
*Indicate Dorado model 1
VERSION[VERLC,0]; VERLC[WRD0@[1000]];

TASKN[EMU,0];	TASKN[FLT,17];

%Three macros define parameters from which constants, small constants,
RM values, or IM data can be constructed:
   MP[NAME,octalstring] makes a parameter of name;
   SP[NAME,P1,P2,P3,P4,P5,P6,P7,P8] makes a parameter NAME equal to the sum
of P1, P2, P3, P4, P5, P6, P7, and P8, where the Pn may be parameters or
integers.
   NSP[NAME,P1,P2,P3,P4,P5,P6,P7,P8] is ones complement of SP.

The parameter "NAME" is defined by the integer "NAME!", so it is ok to
use "NAME" for a constant as well as a parameter.  However, it is illegal
to define constants, small constants, addresses, etc. with identical names.

"Literal" constants such as "322C", "177422C", "32400C", or "32377C"
or literal small constants such as "14S", etc. may be inserted in
microinstructions without previous definition.

Alternatively, constants may be constructed from parameters and integers
using the following macros:
   MC[NAME,P1,P2,P3,P4,P5,P6,P7,P8] defines name as a constant with value =
sum of parameters P1, P2, P3, P4, P5, P6, P7, and P8;
   NMC[NAME,P1,P2,P3,P4,P5,P6,P7,P8] is the ones complement of MC;
   MSC[NAME,P1,P2,P3,P4] defines a small constant.

Note:  MC, NMC, and MSC also define NAME as a parameter.
%

*fields for initializing 20-bit wide memories
F@[E0,0,3]; F@[E1,4,17];

*Macro to initialize 20-bit variables in the target memory.  This is done
*by writing 32100V (i.e., as a literal).
M[V,E1[#1] E0[#2]];

M[!,0];
M[MP,SET[#1!,#2]];
M[PX,IFDEF[#1!,#1!,#1]];
M[DPS,ADD[PX[#1],PX[#2],PX[#3],PX[#4],PX[#5],PX[#6],PX[#7],PX[#8]]];
M[SP,IFG[#0,11,TMARGS@[#1],SET[#1!,DPS[#2,#3,#4,#5,#6,#7,#8,#9]]]];
M[NSP,IFG[#0,11,TMARGS@[#1],SET[#1!,NOT[DPS[#2,#3,#4,#5,#6,#7,#8,#9]]]]];


M[C,IFE[AND[#3#2,177760],0,
  SET[T1@,ADD[LSHIFT[#2,4],RSHIFT[#1,10]]] SET[T2@,AND[#1,377]]
  IFE[T1@,0,BSEL[4]FF256[T2@],
    IFE[T2@,0,BSEL[6]FF256[T1@],
      IFE[T1@,377,BSEL[5]FF256[T2@],
        IFE[T2@,377,BSEL[7]FF256[T1@],ER[Illegal.constant,2]]
      ]
    ]
  ],ER[Constant.too.big,2]]B
];

M[-C,SUB[0,#3#2#1]C];

M[MC,IFG[#0,11,TMARGS@[#1],
  SP[#1,DPS[#2,#3,#4,#5,#6,#7,#8,#9]] M[#1,ADD[#1!]C]]];

M[NMC,IFG[#0,11,TMARGS@[#1],
  SP[#1,NOT[DPS[#2,#3,#4,#5,#6,#7,#8,#9]]] M[#1,ADD[#1!]C]]];

M[S,SET[SC@,#2#1]S@];

M[MSC,IFG[#0,5,TMARGS@[#1],SP[#1,DPS[#2,#3,#4,#5]] M[#1,ADD[#1!]S]]];

%RM stuff

RM constants and variables are allocated in regions defined by:
  RMREGION[RGNNAME]	20-long region

Subsequently, storage can be assigned in that region as follows:
  SETRMREGION[RGNNAME];	begins assigning RM locations in a previously
			declared RMREGION.
  RV[NAME,P1,...,P8];	defines name as an address with initial value
			sum-of-parameters.
  32333R		in a microinstruction creates (if undefined)
			and references a literal.  Duplicating literals
			in other regions is illegal.
  RVN[NAME]		creates name without initial value;
  RVREL[NAME,DISP]	defines a regionless address for references
			relative to the current RBASE.
  RESERVE[N]		skips N (an integer) locations in the current region
			(presumably because RVREL addresses will refer to them)

The assembler checks that the base for an RM address agrees with the value
believed to be in the RBASE register.  This can be declared by:
  KNOWRBASE[RGNNAME]	declares RGNNAME to be in RBASE

  DONTKNOWRBASE		makes all RM addresses out-of-bounds for read references

RBASE can be loaded by:
  RBASE←RBASE[RADDR] -or-	loads RBASE with a small constant whose value
  RBASE←RBASE[RGNNAME]		is the top four bits of RADDR or RGNNAME and
				declares this the current region.
%

*The new RBASE NRB@ is propagated to CRB@ by the IM post-macro
SET[NRB@,0]; *Init for NRB@
M[FIXRBASE@,SET[NRB@,AND[#1,177760]]];
M[KNOWRBASE,SET[Z1@,IFDEF[!#1,!#1,IP[#1]]] FIXRBASE@[Z1@] SET[CRB@,NRB@]];
M[DONTKNOWRBASE,SET[CRB@,-1]SET[NRB@,-1]];
M[RBASE,SET[Z1@,IFDEF[!#1,!#1,IP[#1]]] FIXRBASE@[Z1@] RSHIFT[Z1@,4]S];

%A region is defined by a location counter "!NAME" (an integer).
%
SET[NRGN@,177760];		*address for next region
M[SETRMREGION,SET[NRGN@,!#1] SET[RLAST@,OR[!#1,17]] RM[RLC,!#1]];
M[RMREGION,IFDEF[!#1,ER[#1.already.defined,2],
  IFE[NRGN@,360,ER[Too.many.RM.regions.at.#1,2],
    SET[!#1,ADD[NRGN@,20]] SETRMREGION[#1]]]];

M[RBCK@,IFG[IP[RLC],RLAST@,ER[RM.region.overflow.at.#1,2]]];
M[RV,IFG[#0,11,TMARGS@[#1],
  RBCK@[#1] RLC[#1: DPS[#2,#3,#4,#5,#6,#7,#8,#9]V]]];
M[R,#2#1R(RLC[#2#1R: E1[#1] E0[#2]],
  IFSE[#3,,,ER[#3#2#1R???,2]] RBCK@[#1])];
M[RVN,RBCK@[#1] RM[#1,IP[RLC]] RM[RLC,ADD[IP[RLC],1]]];
M[RESERVE,RM[RLC,ADD[IP[RLC],#1]]];

%STK stuff

STKREGION[NAME,i];	where i = 0 to 3 selects the 100-word STK region
STKWRD[j]		where j = 0 to 77 selects a word in the region
			at which to start allocating storage.
STKVAL[k];		stores k at location selected by STKREGION and
			STKWRD and advances STKWRD by 1.
%

STK[STKLC@,377];	*Init to harmless values
SET[STKBT@,400];
M[STKREGION,IFG[4,#1,SET[STKBT@,LSHIFT[#1,10]],ER[Bad.arg.for.STKREGION,2]]];
M[STKWRD,IFG[100,#1,STK[STKLC@,ADD[#1,STKBT@]],ER[Bad.arg.for.STKWRD,2]]];
M[STKVAL,STKLC@[DPS[#1,#2,#3,#4,#5,#6,#7,#8,#9]V]];

M[EMCK@,BLK[1]RSTK13[#1]ILLIOF@[Stack.op]];
M[UEMCK@,BLK[1]RSTK[#1]ILLIOF@[Stack.op]];

*No StkP=0 underflow check on read because pointer will go negative.
*If also writing STK, write macro will impose the StkP←0 underflow check.
M[STACK&-4,RB(EMCK@[4])];
M[STACK&-3,RB(EMCK@[5])];
M[STACK&-2,RB(EMCK@[6])];
M[STACK&-1,RB(EMCK@[7])];

*With StkP=0 underflow check	*Without StkP=0 underflow check
M[STACK,RB(UEMCK@[10])];	M[STACKNOUFL,RB(UEMCK@[0])];
M[STACK&+1,RB(UEMCK@[11])];	M[STACKNOUFL&+1,RB(UEMCK@[1])];
M[STACK&+2,RB(UEMCK@[12])];	M[STACKNOUFL&+2,RB(UEMCK@[2])];
M[STACK&+3,RB(UEMCK@[13])];	M[STACKNOUFL&+3,RB(UEMCK@[3])];

*These modify the stack pointer after writing, so no check for StkP←0
*is required.
M[STACK&-4←,RB←(EMCK@[4])];
M[STACK&-3←,RB←(EMCK@[5])];
M[STACK&-2←,RB←(EMCK@[6])];
M[STACK&-1←,RB←(EMCK@[7])];
M[STACK&+1←,RB←(EMCK@[1])];
M[STACK&+2←,RB←(EMCK@[2])];
M[STACK&+3←,RB←(EMCK@[3])];

*These modify the stack pointer before writing, so must check for StkP←0
*when decrementing the pointer and must use the ModStkPBeforeW function.
M[STACK-4←,RB←(UEMCK@[14],FF64[27])];
M[STACK-3←,RB←(UEMCK@[15],FF64[27])];
M[STACK-2←,RB←(UEMCK@[16],FF64[27])];
M[STACK-1←,RB←(UEMCK@[17],FF64[27])];
M[STACK←,RB←(UEMCK@[10])];	M[STACKNOUFL←,RB←(UEMCK@[0])];

M[STACK+1←,RB←(EMCK@[1],FF64[27])];
M[STACK+2←,RB←(EMCK@[2],FF64[27])];
M[STACK+3←,RB←(EMCK@[3],FF64[27])];

*For STKP change without reference
M[STKP-4,?(EMCK@[4])];
M[STKP-3,?(EMCK@[5])];
M[STKP-2,?(EMCK@[6])];
M[STKP-1,?(EMCK@[7])];
M[STKP+1,?(EMCK@[1])];
M[STKP+2,?(EMCK@[2])];
M[STKP+3,?(EMCK@[3])];

M[BLOCK,ILLE@[BLOCK]BLK[1]];

M[BREAKPOINT,BRKP[3]];

%Shifter stuff:

Macro to build an RM value that is a shifter descriptor:
  RVSH[name,LMask,RMask,TR,shiftcount] makes an RB constant.
where TR is 0 to 3 to select RR, RT, TR, or TT as left-right
shifter inputs.
%
F@[LMSK@,14,17]; F@[RMSK@,10,13]; F@[TRSL@,2,3]; F@[SCNT@,4,7];
M[RVSH,RBCK@[#1] RLC[(#1: LMSK@[#2]RMSK@[#3]TRSL@[#4]SCNT@[#5])]];

%Compound shift expressions of the forms:
  LSH[X,shiftcount,Y]	RSH[X,shiftcount,Y]
  LDF[X,size,pos,Y]	DPF[X,size,pos,Y]
  RCY[U,V,cyclecount]	LCY[U,V,cyclecount]
where X may be an RM address or T, shiftcount an integer in the range 0 to
17, Y either MD or 0 (defaulted to 0 if omitted), U and V an RM address
and T in either order, and POS the number of bits to the right of the field.
%
M[SHF@,(ASEL[7]BSEL[#1] PD,IFA[FF,FFT@[],
  F1[#2] F2[#3] IFA[COND@,JUFF@[3],UFF@[1]]])];

M[LDF@,(SHF@[IFSE[#1,T,7,4],SUB[20,#2],AND[17,SUB[20,#3]]],#1)];
M[RSH@,(SHF@[IFSE[#1,T,7,4],#2,AND[17,SUB[20,#2]]],#1)];
M[DPF@,(SHF@[IFSE[#1,T,7,4],SUB[20,#2,#3],#3],#1)];
M[LCY@,IFSE[#1,T,
  (IFSE[#2,T,SHF@[7,0,#3],(SHF@[6,0,#3],#2)]),
  (IFSE[#2,T,SHF@[5,0,#3],(SHF@[4,0,#3],#2)],#1)
]];

*RCY reverses args of left cycle unless count = 0
M[RCY,IFG[#0,2,
  ALUF[0]IFE[#3,0,LCY@[#1,#2,0],LCY@[#2,#1,SUB[20,#3]]],NEARGS@[RCY]]];
M[LCY,IFG[#0,2,ALUF[0] LCY@[#1,#2,#3],NEARGS@[LCY]]];
M[RSH,ALUF[IFSE[#3,MD,12,2]] RSH@[#1,#2]];
M[LDF,IFG[#0,2,ALUF[IFSE[#4,MD,12,2]] LDF@[#1,#2,#3],NEARGS@[LDF]]];
M[LSH,ALUF[IFSE[#3,MD,14,4]] (SHF@[IFSE[#1,T,7,4],0,#2],#1)];
M[DPF,IFG[#0,2,ALUF[IFSE[#4,MD,16,6]] DPF@[#1,#2,#3],NEARGS@[DPF]]];

M[XRCY,IFG[#0,2,
  ALUF[1] IFE[#3,0,LCY@[#1,#2,0],LCY@[#2,#1,SUB[20,#3]]],NEARGS@[XRCY]]];
M[XLCY,IFG[#0,2,ALUF[1] LCY@[#1,#2,#3],NEARGS@[XLCY]]];
M[XRSH,ALUF[IFSE[#3,MD,13,3]] RSH@[#1,#2]];
M[XLDF,IFG[#0,2,ALUF[IFSE[#4,MD,13,3]] LDF@[#1,#2,#3],NEARGS@[XLDF]]];
M[XLSH,ALUF[IFSE[#3,MD,15,5]] (SHF@[IFSE[#1,T,7,4],0,#2],#1)];
M[XDPF,IFG[#0,2,ALUF[IFSE[#4,MD,17,7]] DPF@[#1,#2,#3],NEARGS@[XDPF]]];

*Shifter ops assembled as ALU outputs
M[SHFT@,(ALUF[#1] ASEL[7] PD, #2)];

M[SHIFTNOMASK,SHFT@[0,#1]];
M[SHIFTLMASK,SHFT@[2,#1]];
M[SHIFTRMASK,SHFT@[4,#1]];
M[SHIFTBOTHMASKS,SHFT@[6,#1]];
M[SHMDNOMASK,SHFT@[10,#1]];	*Pretty useless--same as SHIFTNOMASK
M[SHMDLMASK,SHFT@[12,#1]];
M[SHMDRMASK,SHFT@[14,#1]];
M[SHMDBOTHMASKS,SHFT@[16,#1]];

M[XSHIFTNOMASK,SHFT@[1,#1]];
M[XSHIFTLMASK,SHFT@[3,#1]];
M[XSHIFTRMASK,SHFT@[5,#1]];
M[XSHIFTBOTHMASKS,SHFT@[7,#1]];
M[XSHMDNOMASK,SHFT@[11,#1]];
M[XSHMDLMASK,SHFT@[13,#1]];
M[XSHMDRMASK,SHFT@[15,#1]];
M[XSHMDBOTHMASKS,SHFT@[17,#1]];

%Stuff for ASEL field and memory references
%

M[ARB@,IFE[FVAL[ASEL],7,FF64[20],ASEL[4]] A];
M[AID@,ASEL[5] ILLIOF@[ID] A];
M[ATT@,IFE[FVAL[ASEL],7,FF64[21],ASEL[6]] A];
*ASEL=7 is shifts, defined earlier
M[AMD@,FF64[22] A];
M[AQ@,FF64[23] A];
M[ASC@,IFG[20,SC@,FF64[SC@],ER[Illegal.A←SC,2]] A];

EQ@[A←Q,AQ@]; EQ@[A←MD,AMD@]; EQ@[A←T,ATT@]; EQ@[A←ID,AID@]; EQ@[A←RB,ARB@]; EQ@[A←SC,ASC@];

M[PRI@,IFE[FVAL[BSEL0],1,,IFA[FA,FAT@[],PF[FA,3]]] A];
M[SEC@,IFA[FA,FAT@[],FA[#1] UFF@[1]]];
M[REF0@,ASEL[0] IFA[FA,FAT@[],FA[#1]UFF@[1]] MM←];
M[REF1@,ASEL[1] IFA[FA,FAT@[],FA[#1]UFF@[1]] MM←];

*Illegal use of an FF>77 to the left of a FETCH←/STORE←RM/T is
*not detected as an error.
M[FETCH←RB,ASEL[1] PRI@];
M[FETCH←T,ASEL[3] PRI@];
M[FETCH←MD,ASEL[3] SEC@[0] A];
M[FETCH←ID,ASEL[3] SEC@[1] A];
M[FETCH←Q,ASEL[3] SEC@[2] A];
M[FETCH←S@,ASEL[1] SEC@[3] ASC@];

M[STORE←RB,ASEL[0] PRI@];
M[STORE←T,ASEL[2] PRI@];
M[STORE←MD,ASEL[2] SEC@[0] A];
M[STORE←ID,ASEL[2] SEC@[1] A];
M[STORE←Q, ASEL[2] SEC@[2] A];
M[STORE←S@,ASEL[0] SEC@[3] ASC@];

M[PREFETCH←,REF0@[0]];
M[MAP←,ILLIO@[MAP←] REF0@[1]];
*MAP← with READMAP function.  Only legal source is RM/STK.
M[RMAP←,ILLIO@[RMAP←] ASEL[0] FF256[131] MM←];
M[IOFETCH←,ILLEF@[IOFETCH←] REF0@[1]];
M[LONGFETCH←,REF0@[2]];

M[DUMMYREF←,REF1@[0]];
M[FLUSH←,ILLIO@[FLUSH←] REF1@[1]];
M[IOSTORE←,ILLEF@[IOSTORE←] REF1@[1]];
M[IFETCH←,ILLIOF@[IFETCH←] REF1@[2]];

M[MM←A,A];
M[MM←RB,A];
M[MM←T,FF64[21] A];
M[MM←MD,FF64[22] A];
M[MM←Q,FF64[23] A];
M[MM←S@,ASC@];


%Stuff for BSEL
%
M[BMD@,BSEL[0]B];	EQ@[B←MD,BMD@];
M[BRB@,BSEL[1]B];	EQ@[B←RB,BRB@];
M[BTT@,BSEL[2]B];	EQ@[B←T,BTT@];
*With FF-controlled shifts the B←Q clause (if any) must be to the left of
*the FF-controlled shift clause.  Haven't thought of an efficient way to
*do this any better.
M[BQ@,IFG[FVAL[BSEL],3,IFE[FVAL[ASEL],7,,ER[BSEL.already.set,2]],BSEL[3]]B];
M[B←Q,BQ@];
*BSEL = 4,5,6,7 are (0,,FF), (377,FF), (FF,,0), and (FF,,377)

%The following macros fix up the LC field according to the R← and T←
selections:
%
M[RERR@,ER[Illegal.R←,2]];
M[RMD@,SELECT[FVAL[LC],PF[LC,4],LC[5],RERR@[],LC[5]FF64[75],,,RERR@[],RERR@[]]MD];
M[RPD@,SELECT[FVAL[LC],PF[LC,6],LC[7],,LC[2],RERR@[],RERR@[],,]];

M[RB←MD,RMD@];
M[RB←B,PD←B(RPD@)];	EQ@[RB←XB,RB←B];
M[RB←T,PD←T(RPD@)];
M[RB←RB,PD←RB(RPD@)];
M[RB←A,PD←A(RPD@)];
M[RB←ID,PD←AID@(RPD@)];
M[RB←PD,PD(RPD@)];
M[RB←Q,PD←Q(RPD@)];
M[RB←S@,PD←ASC@(RPD@)];

M[TERR@,ER[Illegal.T←,2]];
M[TMD@,SELECT[FVAL[LC],PF[LC,3],TERR@[],,,LC[5]FF64[75],TERR@[],LC[2],TERR@[]]MD];
M[TPD@,SELECT[FVAL[LC],PF[LC,1],,TERR@[],TERR@[],LC[5],,LC[7],]];

M[T←MD,TMD@];
M[T←B,PD←B(TPD@)];	EQ@[T←XB,T←B];
M[T←T,PD←T(TPD@)];
M[T←RB,PD←RB(TPD@)];
M[T←A,PD←A(TPD@)];
M[T←ID,PD←AID@(TPD@)];
M[T←PD,PD(TPD@)];
M[T←Q,PD←Q(TPD@)];
M[T←S@,PD←ASC@(TPD@)];

%Stuff for FF decodes 0 to 77:
%

*FF = 0 to 17 are A←small constants, given earlier
*FF= 20 to 23 select A sources, defined with ASEL stuff

M[XORCARRY,FF64[24] ?];
M[XORSAVEDCARRY,FF64[25]?];
M[CARRY20,FF64[26] ?];
*27 is ModStkPBeforeWrite, used implicitly
*30-31 undefined
M[INPUT,FF64[32] PD];
M[INPUTNOPE,FF64[33] PD];
*Makes A←RM/STK, B←RM/STK, and shifter use ID rather than RM/STK
M[RISID,FF64[34]ILLIOF@[RISID] ?];
M[TISID,FF64[35]ILLIOF@[TISID] ?];
M[OUTPUT←,FF64[36] B←];
M[FLIPMEMBASE,FF64[37]?];

*FF = 40 to 57 supply RSTK for write, used implicitly
*FF = 60 to 67 are branch conditions defined with control stuff

* CNT-1 is CNT=0&-1 conditional branch function executed solely for its
* side-effect.  Programmer must force placement of successor instruction at
* an odd location, e.g., by DISPTABLE[1, 1, 1].
M[CNT-1, FF64[63] ?];

M[BIGBDISPATCH←,SOK@[BIGBDISPATCH←] FF64[70] B←];	*B 256-way dispatch
M[BDISPATCH←,SOK@[BDISPATCH←] FF64[71] B←];	*B 8-way dispatch
M[MULTIPLY,FF64[72] ?];
M[Q←,FFBSEL@[73,3] B←];
*74 undefined
*75 is TGETSMD, used implicitly
M[FREEZEBC,FF64[76]?];
M[NOFF,FF[77] ?];	*No operation--only used in default for IM


%Stuff for FF decodes 100 to 377 (unavailable with memory references)
%
M[PCF←,FF256[100] B←];		*PCF←B and start IFU
M[IFUTEST←,FF256[101] B←];
M[IFUTICK,FF256[102] ?];
M[RESCHEDULENOW,FF256[103] ?];
M[ACKJUNKTW←,FF256[104] B←];
M[MEMBASE←B,FF256[105] B];	M[MEMBASE←RB,MEMBASE←BRB@];
  M[MEMBASE←T,MEMBASE←BTT@];	M[MEMBASE←MD,MEMBASE←BMD@];
  M[MEMBASE←Q,MEMBASE←BQ@];
M[RBASE←B,FF256[106] B];	M[RBASE←RB,RBASE←BRB@];
  M[RBASE←T,RBASE←BTT@];		M[RBASE←MD,RBASE←BMD@];
  M[RBASE←Q,RBASE←BQ@];
M[POINTERS←,FF256[107] B←];
*110-117 undefined

*120-121 undefined Mar sources
M[CFLAGS←,FF256[122] A←];		*Source stable on Mar during
					*preceding cycle
M[BRLO←,FF256[123] A←];
M[BRHI←,FF256[124] A←];
M[LOADTESTSYNDROME,FF256[125] ?];	*Loads from DBuf, ties up Mar
M[LOADMCR,(FF256[126] A←#1,B←#2)];	*Some bits from Mar, some from B
M[PROCSRN←,FF256[127] B←];		*Loads from MapBuf, ties up Mar

M[INSSETOREVENT←,FF256[130] B←];	EQ@[MOS←,INSSETOREVENT←];
M[EVENTCNTB←,FF256[131] B←];		EQ@[GENOUT←,EVENTCNTB←];
M[RESCHEDULE,FF256[132] ?];
M[NORESCHEDULE,FF256[133] ?];

M[IFUMRH←,FF256[134] B←];
M[IFUMLH←,FF256[135] B←];
M[IFURESET,FF256[136] ?];
M[BRKINS←,FF256[137] B←];	*BRKINS←B & set BrkPending

M[USEDMD,FF256[140] ?];
M[MIDASSTROBE←,FF256[141] B←];
M[TASKINGOFF,FF256[142] ?];
M[TASKINGON,FF256[143] ?];
M[STKP←,FF256[144] B←];
M[RESTORESTKP,FF256[145]?];
M[CNT←B,FF256[146] B];	M[CNT←RB,CNT←BRB@];
  M[CNT←T,CNT←BTT@];	M[CNT←MD,CNT←BMD@]; M[CNT←Q,CNT←BQ@];
M[LINK←,FF256[147] B←];
M[Q LSH 1,FF256[150] ?];
M[Q RSH 1,FF256[151] ?];
M[TIOA←,FF256[152] B←];
*153 undefined
M[HOLD&TASKSIM←,FF256[154] B←];
M[WF←,FF256[155] A←];
M[RF←,FF256[156] A←];
M[SHC←,FF256[157] B←];

*External B
M[XBOK@,IFA[BSEL,ER[Multiple.B.sources,2],FF256[#1]]];

*From memory external B
M[FAULTINFO',XBOK@[160] XB];
M[PIPE0,XBOK@[161] XB];		EQ@[VAHI,PIPE0];
M[PIPE1,XBOK@[162] XB];		EQ@[VALO,PIPE1];
M[PIPE2',XBOK@[163] XB];
M[PIPE3',XBOK@[164] XB];		EQ@[MAP',PIPE3'];
M[PIPE4',XBOK@[165] XB];		EQ@[ERRORS',PIPE4'];
M[CONFIG',XBOK@[166] XB];
M[PIPE5,XBOK@[167] XB];		EQ@[PREF,PIPE5];

*From IFU external BMux
M[PCX',XBOK@[170] B];
M[EVENTCNTA',XBOK@[171] B];
M[IFUMRH',XBOK@[172] B];
M[IFUMLH',XBOK@[173] B];
M[EVENTCNTB',XBOK@[174] B];

M[DBUF,XBOK@[175] XB];	*From memory external B

*From Control external BMux
M[RWCPREG,XBOK@[176] XB];
M[LINK,XBOK@[177] XB];

%Stuff for small constant functions
%
M[SCFN@,IFG[#1,SC@,FF256[ADD[#2,SC@]],ER[Illegal.arg.for.#3,2]] ?];

M[RBASE←S@,SCFN@[20,200,RBASE←]];
*220-237 are change-RBase-for-write, used implicitly
M[TIOA,IFME[#1,DEVICE,FF256[ADD[AND[IP[#1],7],240]] ?,
  ER[TIOA.arg.not.DEVICE,2]]];
M[MEMBASEX←S@,SCFN@[4,250,MEMBASEX←]];
  M[MEMBASE←BRX@,SCFN@[4,250,MEMBASE←]];
  M[MEMBASEX←BRX@,SCFN@[4,250,MEMBASE←]];
M[MEMBX←S@,SCFN@[4,254,MEMBX←]];

*260-261 undefined
N@[ALUFMRW←]; M[ALUFMRW←B,FF256[262] PD];
  M[ALUFMRW←MD,ALUFMRW←BMD@]; M[ALUFMRW←T,ALUFMRW←BTT@];
  M[ALUFMRW←RB,ALUFMRW←BRB@]; M[ALUFMRW←Q,ALUFMRW←BQ@];
M[ALUFMEM,FF256[263] PD];
M[CNT,FF256[264] PD];
M[POINTERS,FF256[265] PD];
M[TIOA&STKP,FF256[266] PD];
M[SHC,FF256[267] PD];

M[PD RSH 1,FF256[270] PD];	*PD[0]←0
  M[T RSH 1,FF256[270] PD←T];
  M[RB RSH 1,FF256[270] PD←RB];
  M[A RSH 1,FF256[270] PD←A];
  M[ID RSH 1,FF256[270] PD←AID@];
  M[B RSH 1,FF256[270] PD←B];
  M[MD RSH 1,FF256[270] BSEL[0] PD←B];
  *Q RSH 1 through the ALU has to be written (B←Q) LSH 1

M[PD RCY 1,FF256[271] PD];	*PD[0]←ALU[17]
  M[T RCY 1,FF256[271] PD←T];
  M[RB RCY 1,FF256[271] PD←RB];
  M[A RCY 1,FF256[271] PD←A];
  M[ID RCY 1,FF256[271] PD←AID@];
  M[B RCY 1,FF256[271] PD←B];
  M[MD RCY 1,FF256[271] BSEL[0] PD←B];
  M[Q RCY 1,FF256[271] BSEL[3] PD←B];

M[PD BRSH 1,FF256[272] PD];	*PD[0]←ALUcarry
  M[T BRSH 1,FF256[272] PD←T];
  M[RB BRSH 1,FF256[272] PD←RB];
  M[A BRSH 1,FF256[272] PD←A];
  M[ID BRSH 1,FF256[272] PD←AID@];
  M[B BRSH 1,FF256[272] PD←B];
  M[MD BRSH 1,FF256[272] BSEL[0] PD←B];
  M[Q BRSH 1,FF256[272] BSEL[3] PD←B];

M[PD ARSH 1,FF256[273] PD];	*PD[0] unchanged
  M[T ARSH 1,FF256[273] PD←T];
  M[RB ARSH 1,FF256[273] PD←RB];
  M[A ARSH 1,FF256[273] PD←A];
  M[ID ARSH 1,FF256[273] PD←AID@];
  M[B ARSH 1,FF256[273] PD←B];
  M[MD ARSH 1,FF256[273] BSEL[0] PD←B];
  M[Q ARSH 1,FF256[273] BSEL[3] PD←B];

M[PD LSH 1,FF256[274] PD];	*PD[17]←0
  M[T LSH 1,FF256[274] PD←T];
  M[RB LSH 1,FF256[274] PD←RB];
  M[A LSH 1,FF256[274] PD←A];
  M[ID LSH 1,FF256[274] PD←AID@];
  M[B LSH 1,FF256[274] PD←B];
  M[MD LSH 1,FF256[274] BSEL[0] PD←B];
  *Q LSH 1 through the ALU has to be written as (B←Q) LSH 1

M[PD LCY 1,FF256[275] PD];	*PD[17]←ALU[0]
  M[T LCY 1,FF256[275] PD←T];
  M[RB LCY 1,FF256[275] PD←RB];
  M[A LCY 1,FF256[275] PD←A];
  M[ID LCY 1,FF256[275] PD←AID@];
  M[B LCY 1,FF256[275] PD←B];
  M[MD LCY 1,FF256[275] BSEL[0] PD←B];
  M[Q LCY 1,FF256[275] BSEL[3] PD←B];

M[DIVIDE,FF256[276] ?];		*Q[15]←ALUcarry
M[CDIVIDE,FF256[277] ?];	*Q[15]←ALUcarry'

M[MEMBASE←S@,SCFN@[40,300,MEMBASE←]];
  M[MEMBASE←BR@,SCFN@[40,300,MEMBASE←]];
M[CNT←S@,IFE[SC@,20,FF256[340] ?,IFE[SC@,0,ER[Illegal.CNT←,2],
  SCFN@[20,340,CNT←]]]];
M[WAKEUP,IFME[#1,TASKN,FF256[ADD[360,IP[#1]]] ?,ER[Bad.arg.for.WAKEUP,2]]];
M[NOTIFY,FF256[ADD[360,#1]]];

%Placement stuff:

"TOPLEVEL" sets the default branch clause to BRANCH[.+1].
"SUBROUTINE" sets the default to GOTO[.+1].
"ONPAGE" restricts MicroD placement to a single page.
"AUTOPAGE" allows MicroD to place anywhere.
%
M[IMDFLT@,DEFAULT[IM,
  (NOFF,ASEL[4] BSEL[1] W1@[7777] W2@[7777] BRGO@[TS@] GPW0@[ONP@])]];

M[TOPLEVEL,SET[TS@,2] IMDFLT@[]];
M[SUBROUTINE,SET[TS@,1] IMDFLT@[]];

M[ONPAGE,SET[ONP@,ADD[10000,AND[LSHIFT[#1,6],7700]]] IMDFLT@[]];
M[AUTOPAGE,SET[ONP@,0] IMDFLT@[]];

IMLOCK[LK@,0]; F@[BIT0,0,0];
*IMReserve[P,W,N] reserves N words in the microstore beginning at P*100+W,
*so that MicroD won't place any mi there.
M[IMRESERVE,IMLOCK[LK@,ADD[LSHIFT[#1,6],#2]] REPEAT[#3,LK@[BIT0[1]]]];
M[IMUNRESERVE,IMLOCK[LK@,ADD[LSHIFT[#1,6],#2]] REPEAT[#3,LK@[BIT0[0]]]];

%For dispatch tables, DISP[4:17] hold a bit pattern whose 1's constrain
the 0th item in the table to an absolute location with 1's in those
positions.  DISP[24:37] contain a mask of flexible bits in the 0th item
placement.  These must correspond to 0's in DISP[4:17] (Micro checks this).
MicroD will choose an arbitrary value for the flexible bits.  The bits
which may vary in the body of the dispatch table are
	NOR[DISP[4:17],DISP[24:37]].
Each instruction in the dispatch table must specify the value for these
bits using the DAT macro defined below.  MicroD checks that the bits
forced to 1 using DAT were allowed to vary in the body.

Note that each GLOBAL is constrained by a dispatch table with DISP[4:17]
containing 0, and DISP[24:37] containing 7700.  An absolute placement is
constrained by a dispatch table with DISP[4:17] containing the location
and DISP[24:37] containing 0.

**NOT READY YET**

M[DTAB@LE,IFE[AND[#3,#2],0,
  DLC[#1: WRD0@[#2] WRD1@[#3]],ER[Bad.DTAB@LE.call,2]]?];
DTAB@LE[ABS,0,7777];		*Default dispatch table 0 is unconstrained

M[DAT,DTAB@[#1] BEONES@[#2] ?];
M[GLOBAL,DTAB@[DLC] BEONES@[0] DLC[WRD0@[0] WRD1@[7700]] ?];
M[AT,DTAB@[DLC] BEONES@[0] DLC[WRD0@[ADD[#1,#2]] WRD1@[0]] ?];

**INTERIM KLUDGE**
%

M[GLOBAL,GLB@[1]];
M[AT,GPW0@[ADD[IFE[AND[ADD[#1,#2],176077],0,60000,40000],#1,#2]]];

* DISPTABLE[LENGTH, MASK, VALUE]
* appearing in a statement, causes that statement to begin a group of
* LENGTH consecutively-placed statements, 1 <= LENGTH <= 20.
* The first statement is placed so that (address AND MASK) = VALUE.
* MASK defaults to (next power of 2 >= LENGTH)-1, and VALUE defaults to 0.
* Note: it is required that LENGTH+VALUE <= 20.

M[DISPTABLE,SET[T1@,SUB[#1,1]]
  IFE[AND[T1@,177760],0,,ER[DISPTABLE.ill.length]]
  SET[T2@,#2] IFE[T2@,0,
    SET[T3@,T1@] WHILE[T3@,SET[T2@,OR[T2@,T3@]] SET[T3@,RSHIFT[T3@,1]]]]
  IFE[AND[#3,T2@],#3,,ER[DISPTABLE.impossible.constraint]]
  SET[T3@,0] SET[Z1@,0]
  REPEAT[20,IFE[AND[T3@,T2@],#3,SET[Z1@,OR[Z1@,RSHIFT[100000,T3@]]]]
    SET[T3@,ADD[T3@,1]]]
  IMMASK[MASKLC@,IP[ILC]] MASKLC@[CONMSK@[Z1@] DTLEN@[T1@]]
];

*Macro executed after assembling instruction.
*Propagate RBASE change to the next instruction.
M[IMX,SET[CRB@,NRB@]];	SETPOST[IM,IMX];

%Branch macros

FBC will be used for the branch condition, if it is available after the
instruction is assembled, else JCN.  JCN is set at call to BC@ either
when two BC's are given or when IFUJUMP, RETURN, or CORETURN are used.
%
M[BC@,IFA[JCN,FF64[#1],JCN[#2]IFA[FBC,JUFF@[3],PF[FBC,#1]UFF@[1]]]COND@[1]];

%"@" and "~" precede branch condition names for type checking.
Regular BC's					Complementary BC's
%
M[~,];						EQ@[@,~];
M[~ALU=0,BC@[60,0]];				EQ@[@ALU#0,~ALU=0];
M[~ALU<0,BC@[61,1]];				EQ@[@ALU>=0,~ALU<0];
M[~CARRY',BC@[62,2]];				EQ@[@CARRY,~CARRY'];
M[~CNT=0&-1,BC@[63,3]];				EQ@[@CNT#0&-1,~CNT=0&-1];
M[~R<0,BC@[64,4]];				EQ@[@R>=0,~R<0];
M[~R ODD,BC@[65,5]];				EQ@[@R EVEN,~R ODD];
M[~IOATTEN',ILLE@[IOATTEN]BC@[66,6]];		EQ@[@IOATTEN,~IOATTEN'];
M[~RESCHEDULE,ILLIOF@[RESCHEDULE]BC@[66,6]];	EQ@[@RESCHEDULE',~RESCHEDULE];
*OVERFLOW only implemented as a function.
M[~OVERFLOW',FF64[67] COND@[1]];		EQ@[@OVERFLOW,~OVERFLOW'];
*Combination branch conditions
M[~ALU<=0,FF64[60] JCN[1] COND@[1] JUFF@[3]];	EQ@[@ALU>0,~ALU<=0];

M[.,IP[ILC]];
M[.-3,SUB[IP[ILC],3]];	M[.+3,ADD[IP[ILC],3]];
M[.-2,SUB[IP[ILC],2]];	M[.+2,ADD[IP[ILC],2]];
M[.-1,SUB[IP[ILC],1]];	M[.+1,ADD[IP[ILC],1]];

M[DBL@,IFDEF[@#3,W1@[#1] W2@[#2](@#3,@#4),W2@[#1] W1@[#2](~#3,~#4)]];

M[DBLBRANCH,BRGO@[TS@] DBL@[#1,#2,#3,#4]];
M[DBLGOTO,BRGO@[1] DBL@[#1,#2,#3,#4]];
M[DBLCALL,BRGO@[0] RETCL@[1] SOK@[DBLCALL] DBL@[#1,#2,#3,#4]];

M[JMP@,IFDEF[@#2,W1@[#1](@#2,@#3),W2@[#1](~#2,~#3)]];

M[BRANCH,BRGO@[TS@] JMP@[#1,#2,#3]];
M[GOTO,BRGO@[1] JMP@[#1,#2,#3]];
*Complementary BC's illegal on CALL, IFUJUMP, and RETURN.
M[RETURN,(~#1, ~#2, BRGO@[0] RETCL@[2] JCN[107] TLOK@[RETURN])];
M[CORETURN,(~#1, ~#2, BRGO@[0] RETCL@[3] JCN[107] TLOK@[CORETURN])];
*The 2nd BC for IFUJUMP and IFUCALL is illegal but detects errors.
M[IFUJUMP,ILLIOF@[IFUJUMP] IFG[#1,3,ER[Ill.arg.for.IFUJUMP,2],
  BRGO@[0] JCN[ADD[47,LSHIFT[#1,3]]] RETCL@[2] ~#2]];
*IFUCALL is used only on conditional exits when a RETURN is possible.
M[IFUCALL,ILLIOF@[IFUCALL] IFG[#1,2,ER[Ill.arg.for.IFUCALL,2],
  BRGO@[0] JCN[ADD[47,LSHIFT[#1,3]]] RETCL@[3]
  IFSE[#2,,ER[Missing.BC,2],~#2]]];
M[CALL,BRGO@[0] RETCL@[1] SOK@[CALL] IFSE[#2#3,,W1@[#1],W2@[#1](~#2,~#3)]];

*SCALL, DBLSCALL, and SCORETURN must be at an odd location and constrain
*the next 2 instructions in-line to be at .+1 and .+2
M[SCALL,DISPTABLE[3,1,1]CALL[#1,#2,#3]];
M[DBLSCALL,DISPTABLE[3,1,1]DBLCALL[#1,#2,#3,#4]];
M[SCORETURN,DISPTABLE[3,1,1]CORETURN[#1,#2,#3]];

*#1 for external branches is the integer address of the target; unless the
*target is at a Global location, branch conditions are illegal and FF is used.
M[GOTOEXTERNAL,RETCL@[2] BRGO@[0] FF[AND[RSHIFT[#1,4],377]] JCN[AND[#1,17]]
  IFE[TS@,1,IFE[AND[#1,17],0,ER[GotoExternal.call.location]]]];
M[CALLEXTERNAL,RETCL@[3] BRGO@[0] IFE[AND[#1,77],0,JCN[ADD[300,RSHIFT[#1,6]]],
    JCN[AND[#1,17]] FF[AND[377,RSHIFT[#1,4]]]]
  IFE[AND[#1,17],0,,ER[CallExternal.to.goto.location]] SOK@[CallExternal]];
M[BRANCHEXTERNAL,RETCL@[2] BRGO@[0]
  IFE[AND[#1,77],0,JCN[ADD[300,RSHIFT[#1,6]]],
    JCN[AND[#1,17]] FF[AND[377,RSHIFT[#1,4]]]]
  SOK@[BranchExternal.to.Call.loc]];

%IM used as data stuff:

IM words can be assembled as data using the BYT0, BYT1, BYT2, and BYT3
macros defined below.  Each of these sums up to 8 args which are either
parameters or integers, to form the value stored.  BYT0 assembles a 9-bit
value into the position corresponding to READIM[0], and similarly for
BYT1, BYT2, and BYT3.

The way to assemble data is:
	DATA[(BYT0[...] BYT1[...] BYT2[...] BYT3[...] AT[...])];
%

F@[BY0@,0,10];	*RSTK[0:3], ALUF[0:3], BSEL[0]
F@[BY1@,11,20];	*BSEL[1:2], LC[0:2], ASEL[0:2] -- low 8 bits of BYT1
F@[BY2@,21,31];	*BLOCK[0], FF[0:7]
F@[BY3@,32,41];	*JCN[0:7] -- low 8 bits of BYT3
F@[PE020@,42,42]; * high bit of BYT1 XORed with parity of BYT0,,BYT1
F@[PE2141@,43,43]; * high bit of BYT3 XORed with parity of BYT2,,BYT3

M[BYT0,IFG[#0,10,TMARGS@[B0]] SET[B0@, AND[DPS[#1,#2,#3,#4,#5,#6,#7,#8], 777]]];
M[BYT1,IFG[#0,10,TMARGS@[B1]] SET[B1@, AND[DPS[#1,#2,#3,#4,#5,#6,#7,#8], 777]]];
M[BYT2,IFG[#0,10,TMARGS@[B2]] SET[B2@, AND[DPS[#1,#2,#3,#4,#5,#6,#7,#8], 777]]];
M[BYT3,IFG[#0,10,TMARGS@[B3]] SET[B3@, AND[DPS[#1,#2,#3,#4,#5,#6,#7,#8], 777]]];

M[PAR@, SET[T1@, #1]
  SET[T1@, AND[XOR[T1@, RSHIFT[T1@, 4], RSHIFT[T1@, 10], RSHIFT[T1@, 14]], 17]]
  AND[RSHIFT[064626, T1@], 1]];

M[DATA,
  (ILC[(BRGO@[0] RETCL@[2]	*Indicate RETURN so no MicroD fixup
    BY0@[B0@] BY1@[AND[B1@, 377]] BY2@[B2@] BY3@[AND[B3@, 377]]
    PE020@[XOR[PAR@[XOR[B0@, B1@]], 1]]
    PE2141@[XOR[PAR@[XOR[B2@, B3@]], 1]],#1)],
  SET[B0@, 0] SET[B1@, 0] SET[B2@, 0] SET[B3@, 0])];


%IM read/write to/from Link.
"CALLS" is set so next instruction will be at .+1.
"RETURNS" is set so JCN won't be tampered with by MicroD.
%
M[IMWR,JCN[177] BRGO@[0] RETCL@[3] RSTK13[#1] SOK@[IM←] B←];

M[IMLHR0POK←,IMWR[3]];	M[IMLHR0PBAD←,IMWR[7]];
M[IMLHR0'POK←,IMWR[1]];	M[IMLHR0'PBAD←,IMWR[5]];
M[IMRHBPOK←,IMWR[2]];	M[IMRHBPBAD←,IMWR[6]];
M[IMRHB'POK←,IMWR[0]];	M[IMRHB'PBAD←,IMWR[4]];

M[READIM,JCN[167] BRGO@[0] RETCL@[3] RSTK23[#1] SOK@[READIM] ?];


%TPC read/write from Link, address from BMux[14:17]
%
M[LDTPC←,JCN[157] BRGO@[0] RETCL@[3] SOK@[LDTPC←] B←];
M[RDTPC←,JCN[147] BRGO@[0] RETCL@[3] SOK@[RDTPC←] B←];



%"TITLE" outputs the file name and the value of ILC on the .ER file
to help correlate errors with source statements.  It also resets various
assembly flags to standard states.
%
M[MSG@,ER[#1..IM.address.=.,0,IP[ILC]]];
M[NAMSG@,ER[#1..not.assembled,0]];

M[TITLE,IFE[ASMF@,1,
  (SET[XTASK,0] TARGET[ILC] SET[ONP@,0] MSG@[#1] SUBROUTINE),NAMSG@[#1]]];
M[END,(MSG@[#1],
  ILC[(MIDASBREAK: BREAKPOINT, RETURN, AT[7776])],
  SUBROUTINE)];

%IFUM assembly:

INSSET[i,n] declares i (0 to 3) to be the current instruction set
with n (1 to 4) instructions in each IFU entry vector.
Then the following macros are used to define opcodes:

	IFUREG[OPCODE,LEN,MEMB,RBASEB,IFAD,N,SIGN,PA@];
	IFUJMP[OPCODE,LEN,MEMB,RBASEB,IFAD,DISP/SIGN];
	IFUPAUSE[OPCODE,LEN,MEMB,RBASEB,IFAD,N,SIGN,PA@];

MEMB may be either a BRX or BR address symbol; if it is a BRX address,
the MEMB field will be loaded with m = 0 to 3 and MemBase will be loaded with
0.MemBX[0:1].m at the onset of the opcode; if it is a BR address b, then
34 <= b <= 37 is required, the MEMB field will be loaded with m = 4 to 7, and
MemBase will be loaded with 34 to 37 at the onset of the opcode.
For IFUJMP, if LEN is 1, then the 5th arg is the displacement of the
jump (177740 to 37); if LEN is 2, then it is the sign-extend bit.
%

SET[INSN@,0];
M[INSSET,IFG[PX[#1],3,ER[Instruction.set.index.>.3,2],
    SET[INSN@,LSHIFT[PX[#1],10]]]
  IFG[5,PX[#2],IFG[#2,0,
        DEFAULT[IFUM,IFD@[0] NENT@[SUB[PX[#2],1]]],
    ER[Bad.INSSET.call,2]],ER[Bad.INSSET.call,2]]];

M[IFUCK,IFE[#1,#2,IFG[#3,377,ER[Bad.opcode,2],IFUM[IFULC,ADD[INSN@,#3]]],
  ER[Wrong.no.args,2]] SET[T1@,PX[#4]] SET[T2@,AND[3,NOT[T1@]]]
  IFE[T1@,0,ER[Bad.length,2]]];
M[MBIA@,SET[T3@,IP[#1]] IFME[#1,BR,
  IFG[T3@,33,MEMB@[AND[7,T3@]],ER[BR.address.<.34,2]],
  IFME[#1,BRX,MEMB@[T3@],ER[Arg.not.BR.or.BRX.address,2]]
]];
M[IFUREG,IFUCK[#0,10,#1,#2]
  IFULC[TYPE'@[3] LEN'@[T2@] MBIA@[#3] RBASEB'@[XOR[1,#4]] IFD@[#5]
  OP@[PX[#6]] SGN@[PX[#7]] PA@[#8]]];
M[IFUPAUSE,IFUCK[#0,10,#1,#2]
  IFULC[TYPE'@[1] LEN'@[T2@] MBIA@[#3] RBASEB'@[XOR[1,#4]] IFD@[#5]
  OP@[PX[#6]] SGN@[PX[#7]] PA@[#8]]];
M[IFUJMP,IFUCK[#0,6,#1,#2] IFE[T1@,3,ER[Bad.length,2]]
  IFULC[TYPE'@[2] LEN'@[T2@] MBIA@[#3] RBASEB'@[XOR[1,#4]] IFD@[#5]
    SET[T2@,PX[#6]]
    IFE[T1@,1,SGN@[AND[1,RSHIFT[T2@,5]]] PA@[AND[1,RSHIFT[T2@,4]]]
      OP@[AND[T2@,17]], OP@[17] SGN@[T2@]]
  ]
];

%ALU stuff

ALU operations are defined as follows:

	No arg operations (A0 and A1):	ZALUOP
	A-only (A+1, A-1, 2A, 2A+1):	AOP
	Alternative A or B routing:	ABOPA and ABOPB
	Non-arithmetic of two args:	ALUOP
		Synonyms:		XALUOP
	Arithmetic of two args:		SALUOP

Two arg definitions consist of 38 macros which are the product of
	<RB, T, ID, MD, Q, S@, A> OP <RB, T, MD, Q, XB, B>.
Some A and B sources convert immediately into neutrals "A", "B", or "XB".
However, RB, T, MD, Q, and S@ cannot be converted because the routing
is ambiguous, and ID cannot be converted because the instruction
encoding is ambiguous.  This is why so many macros have to be defined.
%

*For emulator-only ALU operations.
M[EPD,ILLIOF@[aluop]PD];

F@[AFLD,0,7];

%Sub-macros used below
 #1 = before A between,
 #2 = after B,
 #3 = ALUF value,
 #4 = text to get A source selected
 #5 = "E" if emulator-only, else blank
%
*Arithmetic (slow) ALU ops use this one
M[SALU@,M[#1RB#2,(BSEL[1]ALUF[#3]#5PD,#4)]
	M[#1T#2,(BSEL[2]ALUF[#3]#5PD,#4)]
	M[#1B#2,(ALUF[#3]#5PD,#4)]
	M[#1MD#2,(BSEL[0]ALUF[#3]#5PD,#4)]
	M[#1Q#2,(ALUF[#3]#5PD,#4,BQ@)]
];
*Logical (fast) ALU ops use this one
M[FALU@,M[#1XB#2,(ALUF[#3]#5PD,#4)]
	SALU@[#1,#2,#3,#4,#5]
];

*XALUOP is the same as ALUOP--used for synonyms
M[XALUOP,FALU@[#1RB#2,#3,#4,ARB@,#5]
	FALU@[#1T#2,#3,#4,ATT@,#5]
	FALU@[#1ID#2,#3,#4,AID@]
	SALU@[#1MD#2,#3,#4,AMD@,#5]
	SALU@[#1Q#2,#3,#4,AQ@,#5]
	SALU@[#1S@#2,#3,#4,ASC@,#5]
	FALU@[#1A#2,#3,#4,,#5]
]

%#1 = before A
 #2 = between
 #3 = after B
 #4 = ALUF value
 #5 = "E" if emulator only, else omitted
 #6 = value for ALUFM RAM
%
*This one for logical (fast) ALU ops
M[ALUOP,ALUFM[ALC,#4] ALC[AFLD[#6]]
	M[AFM#4,#6C]
	XALUOP[#1,#2,#3,#4,#5]
];
*This one for arithmetic (slow) ALU ops
M[SALUOP,ALUFM[ALC,#4] ALC[AFLD[#6]]
	M[AFM#4,#6C]
	SALU@[#1RB#2,#3,#4,ARB@,#5]
	SALU@[#1T#2,#3,#4,ATT@,#5]
	SALU@[#1ID#2,#3,#4,AID@]
	SALU@[#1MD#2,#3,#4,AMD@,#5]
	SALU@[#1Q#2,#3,#4,AQ@,#5]
	SALU@[#1S@#2,#3,#4,ASC@,#5]
	SALU@[#1A#2,#3,#4,,#5]
];

%#1 = name of no-arg op
 #2 = ALUF value
 #3 = value for ALUFM RAM
 #4 = "E" if emulator-only else omitted
%
M[ZALUOP,M[#1,ALUF[#2]#4PD]
	M[AFM#2,#3C]
	ALUFM[ALC,#2] ALC[AFLD[#3]]];

%Operations of one arg which can use either A or B are defined
by both ABOPA and ABOPB.  They prefer B for RB, T, MD, and Q.
  #1 = before "A"
  #2 = after "A"
  #3 = ALUF value
  #4 = value for ALUFM #3
***BUG: The "A" operation is arithmetic but used with XORCARRY, cannot
guarantee that the source is not routed over B instead.
%
M[ABOPA,M[#1T#2,#1(IFA[BSEL,ATT@,BTT@])#2]
	M[#1ID#2,#1(AID@)#2]
	M[#1S@#2,#1(ASC@)#2]
	M[#1A#2,ALUF[#3]PD]
	ALUFM[ALC,#3] ALC[AFLD[#4]]
	M[AFM#3,#4C]
];

M[ABOPB,M[#1RB#2,#1(IFA[BSEL,ARB@,BRB@])#2]
	M[#1MD#2,#1(IFA[BSEL,AMD@,BMD@])#2]
	M[#1Q#2,#1(IFA[BSEL,AQ@,BQ@])#2]
	M[#1B#2,ALUF[#3] PD]
	M[#1XB#2,ALUF[#3] PD]
	ALUFM[ALC,#3] ALC[AFLD[#4]]
	M[AFM#3,#4C]
];

%A-only operations
  #1 = before
  #2 = after
  #3 = ALUF value
  #4 = value for ALUFM #3
  #5 = "E" if emulator-only, else omitted
%
M[AOP,	ALUFM[ALC,#3] ALC[AFLD[#4]]
	M[AFM#3,#4C]
	XAOP[#1,#2,#3,#4,#5]
];

*Same as AOP, used for synonyms
M[XAOP,	M[#1T#2,#1(ATT@)#2]
	M[#1RB#2,#1(ARB@)#2]
	M[#1ID#2,#1(AID@)#2]
	M[#1MD#2,#1(AMD@)#2]
	M[#1Q#2,#1(AQ@)#2]
	M[#1S@#2,#1(ASC@)#2]
	M[#1A#2,ALUF[#3]#5PD]
];