Dragon Opcodes To DragonCore^.pa Date August 23, 1984 From Russ Atkinson Location PARC Subject Dragon Opcodes Organization CSL XEROX Release as [Indigo]Doc>DragOps.tioga Last edited by Russ Atkinson, August 23, 1984 9:51:57 am PDT Abstract This document describes the Dragon instruction set as seen by the machine code programmer and compiler builder. Dragon Opcodes This document is a DRAFT, and most of the information in it is volatile. This document is also INCOMPLETE, and should be viewed with some suspicion. Revisions are currently being sent through Russ Atkinson. Introduction The Dragon is a multi-processor general purpose computer currently under development in the Computer Science Laboratory at Xerox PARC. Most of the parts will will be fabricated in custom CMOS. The Dragon will have a shared address space of 2^32 32-bit words. It should have very high performance at relatively low cost. Each Dragon processor has two logical parts, the IFU (instruction fetch unit) and the EU (execution unit). The IFU fetches instructions and directs the EU to perform arithmetic, logical, shifting, fetching, and storing operations. There are also two caches on memory, one for the IFU and one for the EU. A Dragon word is 32-bits wide. In this document we follow the Mesa convention of numbering the bits from left to right, so that the most significant bit has index 0, and the least significant bit has index 31. This corresponds to the Mesa declaration: Word: TYPE = PACKED ARRAY [0..32) OF BOOL; The remainder of this document assumes some familiarity with the Mesa language, since we use it to describe data formats and the effect of instructions. There are some changes associated with putting Mesa on Dragon, detailed in [Indigo]Doc>DragonMesaChanges.tioga. EU state The EU performs various operations on local registers, and communicates with the outside world through a cache attached to a bus (the M-bus). The EU has a 32-bit ALU, a Field Unit (FU) for shifting and other field operations, and a multiplier unit. The EU has a set of registers that contain the most recent elements of the data stack for a process. There are also registers that contain constants, as well as special purpose quantities. This architecture permits most elementary operations invloving local variables to be performed in 1 EU cycle. However, this architecture requires special attention to migrating the contents of a process stack between registers and memory. The EU has the following registers: Stack denotes the stack registers (ARRAY [0..StackSize) OF Word) StackSize = 128 in current version. Locals denotes the local registers (Locals[x] == Stack[(x+L) MOD StackSize]) note that Locals is aliased with Stack. AuxRegs denotes the auxilliary registers (ARRAY [0..15] OF Word). Most of these registers will be used for runtime support for higher-level languages (i.e. Mesa). Constants is an array of registers in the EU (ARRAY [0..11] OF Word). Although these registers are not really constant as far as the hardware is concerned, they are used to hold constants in the Mesa runtime. They are more general than the AuxRegs in that they can be used in more addressing modes. Field denotes a special register that can be used to control the field unit operations, and also participates in multiplication and division. MAR (Memory Address Register) denotes the register which holds the address given in the last memory operation. It is used to report EU page faults. IFU state The IFU turns a stream of variable-length instructions into signals that control the EU. It also performs address calculations used for jumps, calls and returns. The IFU contains a small stack of the most recent procedure contexts. A procedure context for the IFU is simply a program counter (PC) and an index into the EU stack giving the base of the local variables. The IFU has the following registers (actually more than these, but for simplicity): PC is the program counter (a byte address). Instruction space is limited to 2^32 bytes (roughly 4 gigabytes), even though the full Dragon address space is 2^32 words. S is the stack pointer (an index into Stack). Many instructions take operands implicitly using the stack. Procedure calls use the stack for arguments and returns. L gives the base of the local frame (an index into Stack). The first 16 registers at or above L are easily addressable through Dragon instructions. SLimit gives the limit for S. A stack overflow occurs when S is incremented to reach SLimit. Instruction formats This section describes the various instruction formats. Note that the description [0..255] specifies an unsigned number occupying 8 bits, while [-128..127] specifies a signed number occupying 8 bits. The description of the instruction format gives tentative bit assignments, followed by a list of the instructions using the format (in {} brackets), followed by a rough description of how the format is interpreted. Arithmetic involving S or L will always be performed modulo the size of the EU stack, without detection of underflow or overflow. We will not further indicate this limitation of precision. For convenience, we use the following abbreviations to refer to numbers obtained from bytes that follow the opcode byte: Alpha is the first byte after the opcode. AlphaZ is Alpha extended to 32 bits with high-order 0s. AlphaS is Alpha extended to 32 bits with the sign (high-order) bit of Alpha. Beta is the second byte after the opcode. BetaZ is Beta extended with 0s. When taken as a pair of four bit numbers, BetaL is the leftmost half of Beta, and BetaR is the rightmost half. Gamma is the third byte after the opcode. Delta is the fourth byte after the opcode. AlphaBeta is the unsigned unaligned halfword following the opcode byte, interpreted as Alpha + Beta*256. AlphaBetaZ is AlphaBeta extended to 32 bits with 0s. AlphaBetaS is AlphaBeta extended to 32 bits with the sign (high-order) bit of AlphaBeta. AlphaBetaGammaDelta is the 32-bit unsigned unaligned quantity following the opcode byte. The number is interpreted as AlphaBeta + 256*256*(Gamma + Delta*256). OI - Operation Implicit [op: [0..255]] -- 1 byte {ADD, BNDCK, DIS, DUP, EXCH, EXDIS, J1, LCn, MDIV, MUL, RDIV, RETN, RETT, SFC, SFCI, SJ, SUB, UDIV, UMUL} For OI instructions the operand (if any) is implicit in the opcode. OB - Operation Byte [op: [0..255], lit: [0..255]] -- 2 bytes {ADDB, ARL, AS, ASL, CST, EP, IN, J2, JB, LEUR, LIB, LIFUR, OUT, PSB, RB, RET, RSB, SEUR, SIFUR, SUBB, WB, WSB} For OB instructions the operand is given by AlphaZ or AlphaS. ODB - Operation Double Byte [op: [0..255], lit: [0..65535]] -- 3 bytes {ADDDB, FSDB, J3, JDB, LFC, LGF, LIDB, SHL, SHR} For ODB instructions the operand is given by AlphaBetaZ or AlphaBetaS. OQB - Operate Quad Byte [op: [0..255], addr: Word] -- 5 bytes {DFC, J5, LIQB} For OQB instructions the operand is AlphaBetaGammaDelta. JBB - Jump Byte Byte [op: [0..255], dist: [-128..127], lit: [0..255]] -- 3 bytes {JEBB, JEBBJ, JNEBB, JNEBBJ} For JBB instructions the new PC is the byte address given by PC+AlphaS. BetaZ is used for comparison with the top of stack. LR - Local Register [op: [0..15], reg: [0..15]] -- 1 byte {LRn, SRn} For LR instructions the operand is Locals[reg], which is either pushed to or popped from the stack. LRB - Local Register Byte [op: [0..15], reg: [0..15], disp: [0..255]] -- 2 bytes {LRIn, SRIn} For these instructions, the operand is (Locals[reg]+AlphaZ)^, which is either pushed to or popped from the stack. LRRB - Local Register Register Byte [op: [0..255], disp: [0..255], reg1,reg2: [0..15]] -- 3 bytes {RAI, RRI, WAI, WRI} For all instructions, reg1 (BetaL) indicates a local register. For RRI and WRI, reg2 (BetaR) indicates a local register as well. For RAI and WAI, reg2 indicates an auxilliary register. RR - Register to Register [op: [0..255], c,a: [0..15], aOpt,cOpt,bOpt,aux: BOOL, b: [0..15]] -- 3 bytes {RADD, RAND, RBC, RFU, ROR, RRX, RSUB, RUADD, RUSUB, RVADD, RVSUB, RXOR} For these instructions the effect is roughly Rc_Ra op Rb. SE is used to indicate the effect of the instruction on S. SE_0 at the start of the instruction, and S_S+SE at the end of the instruction. Ra: IF NOT aOpt THEN IF aux THEN AuxRegs[a] ELSE Locals[a] ELSE SELECT a FROM < 12 => Constants[a] 12 => Stack[S]; 13 => Stack[S-1]; 14 => Stack[S]; SE_SE-1 15 => Stack[S-1]; SE_SE-1 Rb: IF NOT bOpt THEN IF aux THEN AuxRegs[b] ELSE Locals[b] ELSE SELECT b FROM < 12 => Constants[b] 12 => Stack[S]; 13 => Stack[S-1]; 14 => Stack[S]; SE_SE-1 15 => Stack[S-1]; SE_SE-1 Rc: IF NOT cOpt THEN IF aux THEN AuxRegs[c] ELSE Locals[c] ELSE SELECT c FROM < 12 => Constants[c] 12 => Stack[S]; 13 => Stack[S-1]; 14 => Stack[S+1]; SE_SE+1 15 => Stack[S+1]; SE_SE+1 RJB - Register Jump Byte [op: [0..255], dist: [-128..127], sdd,sd,opt,aux: BOOL, reg: [0..15]] -- 3 bytes {RJEB, RJEBJ, RJGB, RJGBJ, RJGEB, RJGEBJ, RJLB, RJLBJ, RJLEB, RJLEBJ, RJNEB,RJNEBJ} For these instructions the effect is to jump to the byte PC given by PC+AlphaS if the indicated comparision of Ra with Rb is true. Beta is decoded as much as possible in the same way that Beta is decoded for the RR format instructions. The comparision is always made involving either [S] or [S-1] with a register determined by the decoding of Beta. SE is used as in the RR format description. IF sdd THEN SE_SE-1 Ra: IF sd THEN Stack[S-1] ELSE Stack[S] Rb: IF NOT opt THEN IF aux THEN AuxRegs[reg] ELSE Locals[reg] ELSE SELECT reg FROM < 12 => Constants[reg] 12 => Stack[S]; 13 => Stack[S-1]; 14 => Stack[S]; SE_SE-1 15 => Stack[S-1]; SE_SE-1 Instruction descriptions The following is a list of the instructions currently planned for the first version of the Dragon IFU. This instruction set is relatively sparse, to leave room for more advanced IFUs. Notation [x] means the contents of EU register x. Hence [S-1] is the second word on the stack (arithmetic within square brackets is performed modulo the stack size). S is the stack pointer and L is the Register Local pointer (so [L+1] is register local 1). (y)^ is the contents of memory location y. Loads and Stores Name format opcodes DUP OI 1 DUPlicate. [S+1]_[S]; S_S+1. EXCH OI 1 EXCHange. temp_[S]; [S]_[S-1]; [S-1]_temp. EXDIS OI 1 EXCHange discard. [S-1]_[S]; S_S-1. LCn OI 8 Load Constant n. [S+1]_Constants[n]; S_S+1. n indicates one of the first 8 constant registers. LIB OB 1 Load Immediate Byte. [S+1]_AlphaZ; S_S+1. LIDB ODB 1 Load Immediate Double Byte. [S+1]_AlphaBetaZ; S_S+1. LIQB OQB 1 Load Immediate Quad Byte. [S+1]_AlphaBetaGammaDelta; S_S+1. LIQB is useful for loading 32-bit constants. LRn LR 16 Load Register n. [S+1]_[L+n]; S_S+1. SRn LR 16 Store Register n. [L+n]_[S]; S_S-1. Reads & Writes Name format opcodes LGF ODB 1 1 Load Global Frame. [S+1]_([GB]+AlphaBetaZ)^; S_S+1. This operation is used to load global frames. GB denotes auxilliary register 0 in the EU. Unfortunately we have to have a global frame table, but at least it is quite large (64K frames). The decision to use this instruction is not entirely final, since LIQB may be preferable. LRIn LRB 16 Load Register Indirect n. [S+1]_([L+n]+AlphaZ)^; S_S+1. PSB OB 1 Put Swapped Byte. ([S-1]+AlphaZ)^_[S]; S_S-1. RAI LRRB 1 Read Auxilliary register Indirect. [L+BetaL]_(AuxRegs[BetaR]+AlphaZ)^. RB OB 1 Read Byte. [S]_([S]+AlphaZ)^. RRI LRRB 1 Read Register Indirect. [L+BetaL]_([L+BetaR]+AlphaZ)^. RRX RR 1 Read Register indeXed. [Rc]_([Ra]+[Rb])^. RSB OB 1 Read Save Byte. [S+1]_([S]+AlphaZ)^; S_S+1. SRIn LRB 16 Store Register Indirect n. ([L+n]+AlphaZ)^_[S]; S_S-1. WAI LRRB 1 Write Auxilliary register Indirect. (AuxRegs[BetaR]+AlphaZ)^_[L+BetaL]. WB OB 1 Write Byte. ([S]+AlphaZ)^_[S-1]. S_S-2. WRI LRRB 1 Write Register Indirect. ([L+BetaR]+AlphaZ)^_[L+BetaL]. WSB OB 1 Write Swapped Byte. ([S-1]+AlphaZ)^_[S]; S_S-2. Arithmetic and logical All arithmetic is performed using 32-bit 2s-complement arithmetic. Provisions are made for extended precision arithmetic by using Carry for some instructions. Integer overflow is detected and trapped for most arithmetic. Overflow is defined to occur for addition if the two operands have equal sign and the sign of the result is not equal to the sign of the operands. Overflow cannot occur for addition if the operand signs differ. Overflow is defined for subtraction by considering it to be addition with modified operands. Some langauges, especially Lisp, need to distinguish between numbers and addresses within a word. The convention in Dragon is to provide checking for Lisp NaN (Not a Number), which is defined to occur when the two top bits of a word are not equal. Lisp NaN checking is performed on both operands and results. Name format opcodes ADD OI 1 ADD. [S-1]_[S]+[S-1]; S_S-1. Carry is not used or set. Trap on integer overflow. ADDB OB 1 Add Byte. [S]_[S]+AlphaZ. Carry is not used or set. Trap on integer overflow. ADDDB ODB 1 Add Double Byte. [S]_[S]+AlphaBetaZ. Carry is not used or set. Trap on integer overflow. BNDCK OI 1 BouNDs ChecK. Bounds Check trap if [S-1] < 0 OR [S-1]-[S] >= 0; S_S-1. No change to Carry. This instruction is used to check indexes against bounds. It is also used when a number is narrowed to fit into a subrange. MDIV OI 1 Modulus DIVide. [S-2],[S-1] = [S-2],[S-1] MDIV [S]; S_S-1. Initially, x = [S-2],[S-1] (most significant word in [S-2]), y = [S], then [S-2] _ q; [S-1] _ r; where x = q*y + r, and |r| < |y|, and Sign[r] = Sign[y]. Integer overflow trap on overflow or divide by zero. MUL OI 1 MULtiply. [S-1],[S] _ [S-1]*[S]. Signed multiplication, 32x32 -> 64 bits. No traps possible. RADD RR 1 Register ADD. Rc_Ra+Rb+Carry. Carry_0. Trap on integer overflow. RAND RR 1 Register AND. Rc_Ra AND Rb. RBC RR 1 Register Bounds Check. Bounds Check trap if Ra < 0 OR Ra - Rb >= 0; Rc_Ra. No change to Carry. Note: if Rb = FIRST[INT], RBC will fault when Ra < 0, which is useful for assignments between INT and CARD. RDIV OI 1 Remainder DIVide. [S-2],[S-1] = [S-2],[S-1] RDIV [S]; S_S-1. Initially, x = [S-2],[S-1] (most significant word in [S-2]), y = [S], then [S-2] _ q; [S-1] _ r; where x = q*y + r, and |r| < |y|, and Sign[r] = Sign[x]. Integer overflow trap on overflow or divide by zero. RLADD RR 1 Register Lisp ADD. Rc_Ra+Rb. Carry_0. Trap on integer overflow or Lisp NaN. RLSUB RR 1 Register Lisp SUBtract. Rc_Ra-Rb. Carry_0. Trap on integer overflow or Lisp NaN. ROR RR 1 Register OR. Rc_Ra OR Rb. RSUB RR 1 Register SUBtract. Rc_Ra-Rb-Carry. Carry_0. Trap on integer overflow. RUADD RR 1 Register Unsigned ADD. Rc_Ra+Rb+Carry. Carry_adder CarryOut. No trap. RUSUB RR 1 Register Unsigned SUBtract. Rc_Ra-Rb-Carry. Carry_NOT[adder CarryOut]. No trap. RVADD RR 1 Register Vanilla ADD. Rc_Ra+Rb. Carry not affected. No trap. RVSUB RR 1 Register Vanilla SUBtract. Rc_Ra-Rb. Carry not affected. No trap. RXOR RR 1 Register XOR. Rc_Ra XOR Rb. SUB OI 1 SUBtract. [S-1]_[S-1]-[S]; S_S-1. Carry is not used or set. Trap on integer overflow. SUBB OB 1 Subtract Byte. [S]_[S]-AlphaZ. Carry is not used or set. Trap on integer overflow. UDIV OI 1 Unsigned DIVide. [S-2],[S-1] = [S-2],[S-1] UDIV [S]; S_S-1. Initially, x = [S-2],[S-1] (most significant word in [S-2]), y = [S], then [S-2] _ q; [S-1] _ r; where x = q*y + r, and r < y. x,y,q, and r are treated as unsigned numbers. Integer overflow trap on overflow or divide by zero. UMUL OI 1 Unsigned MULtiply. [S-1],[S] _ [S-1]*[S]. Unsigned multiplication, 32x32->64 bits. No traps possible. Field unit operations Name format opcodes FSDB ODB 1 Field Setup Double Byte. Field_AlphaBeta. Stores AlphaBeta to Field to setup the field descriptor for a field unit operation. RFU RR 1 Register Field Unit. Rc_FieldUnit[Ra, Rb, Field]. This a general shift operation, including extract, insert, and shift. The Field register supplies the field descriptor. SHL ODB 1 SHift Left. [S]_FieldUnit[[S], 0, AlphaBeta]. This operation shifts and masks single words according to the field descriptor in AlphaBeta. It is especially useful for shifting left. SHR ODB 1 SHift Right. [S]_FieldUnit[[S], [S], AlphaBeta]. This operation shifts and masks single words according to the field descriptor in AlphaBeta. It is especially useful for shifting right, rotating, and extracting fields. IFU index adjusting instructions Name format opcodes AL OB 1 Add to L. L_L+AlphaZ. This instruction is especially useful for saving and restoring stack frames, but may have other exotic uses. AS OB 1 Add to Stack. S_S+AlphaZ. Stack overflow is not checked by this instruction, so it is primarily useful for discarding words from the stack. ASL OB 1 Add to Stack from L. S_L+AlphaZ. Stack overflow is not checked by this instruction, so it is primarily useful for discarding words from the stack when the distance from L is known, but S could be at any level. DIS OI 1 DIScard. S_S-1. EP OB 1 Enter Procedure. L_S+Alpha. This instruction is used at procedure entry to establish the base of the local frame. Unconditional jumps Name format opcodes DJ OQB 1 Direct Jump. PC_AlphaBetaGammaDelta. JB OB 1 Jump Byte. PC_PC+AlphaS. JDB ODB 1 Jump Double Byte. PC_PC+AlphaBetaS. Jn O* 4 n IN {1, 2, 3, 5}. Jumps to byte address PC+n. These jump instructions are implemented as null operations for speed. J4 is not an opcode because there are no 4 byte opcodes. SJ OI 1 Stack Jump. PC_PC+[S]. S_S-1. This operation is useful for computed jumps. Conditional jumps Each of the following conditional jumps takes two opcodes: one where the prediction is to not jump (no trailing J to the opcode), and one where the prediction is to jump (a trailing J to the opcode). Comparison treats the two numbers as 32-bit signed numbers, unsigned comparisons being judged less common. Name format opcodes JEBB(J) JBB 2 Jump Equal Byte Byte. IF BetaZ = [S] THEN PC_PC+AlphaS. S_S-1. JNEBB(J) JBB 2 Jump Not Equal Byte Byte. IF BetaZ # [S] THEN PC_PC+AlphaS. S_S-1. RJEB(J) RJB 2 Register Jump Equal Byte. IF Ra=Rb THEN PC_PC+AlphaS. RJGB(J) RJB 2 Register Jump Greater Byte. IF Ra>Rb THEN PC_PC+AlphaS. RJGEB(J) RJB 2 Register Jump Greater Equal Byte. IF Ra>=Rb THEN PC_PC+AlphaS. RJLB(J) RJB 2 Register Jump Less Byte. IF Ra= 0; S_S-1 CST OB 1 [S+1]_([S-2]+AlphaZ)^; [S+1]=[S] => ([S-2]+AlphaZ)^_[S-1]; S_S+1; special: atomic DFC OQB 1 call proc at AlphaBetaGammaDelta DIS OI 1 S_S-1 DJ OQB 1 PC _ AlphaBetaGammaDelta DUP OI 1 [S+1]_[S]; S_S+1 EP OB 1 L_S+Alpha EXCH OI 1 [S+1]_[S]; [S]_[S-1]; [S-1]_[S+1] EXDIS OI 1 [S-1]_[S]; S_S-1 FSDB ODB 1 Field_AlphaBeta IN OB 1 [S]_([S]+AlphaZ)^; special: uses IO lines JB OB 1 PC_PC+Alpha JDB ODB 1 PC_PC+AlphaBetaS JEBBj JBB 2 BetaZ = [S] => PC_PC+AlphaS; S_S-1 Jn O* 4 Noop of length 1, 2, 3, or 5 bytes (used as jump) JNEBBj JBB 2 BetaZ # [S] => PC_PC+AlphaS; S_S-1 LCn OI 8 [S+1]_Constants[n]; S_S+1 LEUR OB 1 [S+1]_PReg[Alpha]; S_S+1 LFC JDB 1 call proc at PC+AlphaBetaS LGF ODB 1 [S+1]_([GB]+AlphaBetaZ)^; S_S+1 LIB OB 1 [S+1]_AlphaZ; S_S+1 LIDB ODB 1 [S+1]_AlphaBetaZ; S_S+1 LIFUR OB 1 [S+1]_PReg[Alpha]; S_S+1 LIQB OQB 1 [S+1]_AlphaBetaGammaDelta; S_S+1 LRIn LRB 16 [S+1]_([L+n]+AlphaZ)^; S_S+1 LRn LR 16 [S+1]_[L+n]; S_S+1 MDIV OI 1 [S-2],[S-1] _ [S-2],[S-1] / [S]; signed, Sign[rem] = Sign[divisor] MUL OI 1 [S-1],[S] _ [S-1]*[S]; signed OUT OB 1 ([S]+AlphaZ)^_[S-1]; S_S-2; special: uses IO lines PSB OB 1 ([S-1]+AlphaZ)^_[S]; S_S-1 RADD RR 1 Rc_Ra+Rb+carry; carry_0; trap on overflow RAI LRRB 1 [L+BetaL]_(AuxRegs[BetaR]+AlphaZ)^ RAND RR 1 Rc_Ra AND Rb RB OB 1 [S]_([S]+AlphaZ)^ RBC OB 1 trap if Ra < 0 OR Ra-Rb>= 0; Ra_Rc RDIV OI 1 [S-2],[S-1] _ [S-2],[S-1] / [S]; signed, Sign[rem] = Sign[dividend] RET OB 1 S_L+Alpha; return from proc RETN OB 1 return from proc RETT OB 1 return from proc; enable traps RFU RR 1 [Rc]_FieldUnit[[Ra],[Rb],Field] RJEBj RJB 2 Ra=Rb => PC_PC+AlphaS RJGBj RJB 2 Ra>Rb => PC_PC+AlphaS RJGEBj RJB 2 Ra>=Rb => PC_PC+AlphaS RJLBj RJB 2 Ra PC_PC+AlphaS RJLEBj RJB 2 Ra<=Rb => PC_PC+AlphaS RJNEBj RJB 2 Ra#Rb => PC_PC+AlphaS RLADD RR 1 Rc_Ra+Rb; carry_0; trap on overflow or Lisp NaN RLSUB RR 1 Rc_Ra-Rb; carry_0; trap on overflow or Lisp NaN ROR RR 1 Rc_Ra OR Rb RRI LRRB 1 [L+BetaL]_([L+BetaR]+AlphaZ)^ RRX RR 1 [Rc]_([Ra]+[Rb])^ RSB OB 1 [S+1]_([S]+AlphaZ)^; S_S+1 RSUB RR 1 Rc_Ra-Rb-carry; carry_0; trap on overflow RUADD RR 1 Rc_Ra+Rb+carry; set carry RUSUB RR 1 Rc_Ra-Rb-carry; set carry RVADD RR 1 Rc_Ra+Rb RVSUB RR 1 Rc_Ra-Rb RXOR RR 1 Rc_Ra XOR Rb SEUR OB 1 PReg[Alpha]_[S]; S_S-1 SFC OI 1 call proc at [S]; S_S-1 SFCI OI 1 call proc at ([S])^ SHL ODB 1 [S]_FieldUnit[[S],0,AlphaBeta] SHR ODB 1 [S]_FieldUnit[[S],[S],AlphaBeta] SIFUR OB 1 PReg[Alpha]_[S]; S_S-1 SJ OI 1 PC_PC+[S] SRIn LRB 16 ([L+n]+AlphaZ)^_[S]; S_S-1 SRn LR 16 [L+n]_[S]; S_S-1 SUB OI 1 [S-1]_[S-1]-[S]; S_S-1; trap on overflow SUBB OB 1 [S]_[S]-AlphaBetaZ; trap on overflow WAI LRRB 1 (AuxRegs[BetaR]+AlphaZ)^_[L+BetaL] WB OB 1 ([S]+AlphaZ)^_[S-1]; S_S-2 WRI LRRB 1 ([L+BetaR]+AlphaZ)^_[L+BetaL] WSB OB 1 ([S-1]+AlphaZ)^_[S]; S_S-2 UDIV OI 1 [S-2],[S-1] _ [S-2],[S-1] / [S]; unsigned UMUL OI 1 [S-1],[S] _ [S-1]*[S]; unsigned Sample code sequences Notation In the following examples, FD[insert,mask,shift] denotes a field descriptor with indicated fields. RR format operations are written with the operands in the order Ra,Rb,Rc. Packed sequence fetch/store Assume the following Cedar/Mesa code: r: REF TEXT; -- in local register Lr (32-bit maxLength in word 1) i: INT; -- in local register Li c: CHAR; -- in local register Lc c _ r[i]; -- generates the following code {11 cycles, 26 bytes} LRI Lr,1 -- push the word containing the bound RBC Li,[S],[S] -- bounds check the index given (leave Li on stack) SHR FD[0,30,30] -- make a word index RADD [S],Lr,[S] -- get the word address (-1) RB 2 -- fetch the word containing the desired char LR Li -- push the character index SHL FD[0,5,3] -- make it a bit index into the word ADDDB FD[0,8,8] -- add in the rest of the field descriptor SEUR Field -- set the Field register to control the shift RFU [S]-,C0,Lc -- extract the char and store it to c r[i] _ c; -- generates the following code {14 cycles, 32 bytes} LRI Lr,1 -- push the word containing the bound RBC Li,[S],[S] -- bounds check the index given (leave Li on stack) SHR FD[0,30,30] -- make a word index RADD [S],Lr,[S] -- get the word address (-1) RSB 2 -- fetch the array word (leave addr on stack) LIDB FD[1,32,24] -- push the base field desc LR Li -- push the character index SHL FD[0,5,3] -- make it a bit index into the word SHR FD[1,10,5] -- also insert it into the mask position SUB -- adjust the field descriptor SEUR Field -- set the Field register to control the shift RFU Lc,[S],[S] -- insert the char into the array word WSB 2 -- store the changed word Procedure body & call AddFunny: PROC [x,y: INT] RETURNS [INT] = { z: INT _ x+y; IF z > 1 THEN z _ z + z; RETURN [z]; }; EP 377B -- point L at x RADD Lx,Ly,[S+1]+ -- z: INT _ x+y RJLEB 6,[S],C1 -- IF z > 1 THEN RADD Lz,Lz,Lz -- z _ z + z ROR Lz,Lz,Lx -- RETURN [z] RET 0 -- (S _ L+0) u _ AddFunny[v, w] + 1; LR Lv -- push v LR Lw -- push w DFC AddFunny -- AddFunny[v, w] RADD [S-1]-,C1,Lu -- u _ ... + 1 Arithmetic precision changes Multiple-precision arithmetic quantities are stored with higher order words in lower addresses, even within the register stack. That is, the word at [S-1] is more significant than the word at [S]. Double precision numbers show up in multiplication and division. DUP -- low-order word on top of stack RUADD [S-1],[S],[S] -- carry bit _ sign bit & put garbage in [S-1] RSUB C0,C0,[S-1] -- negate sign bit into high-order word, clear the carry RUADD [S]-,[S],[S+1]+ -- carry _ sign bit of low order word, garbage at [S+1] RADD [S-1],C0,[S+1]+ -- [S+1]+ _ sign bit plus high-order word RBC [S]-,C1,[S] -- bounds check fault when [S] # 0, pop stack EXDIS -- flush the high-order word RXOR [S+1]+,C0,[S] -- push NOT of the number SHR FD[0,17,0] -- isolate high bits of number ADDDB 100000B -- bump the sign, which carries through ROR [S-1],[S]-,[S-1] -- OR back the extension DUP SHR FD[0,17,0] -- isolate the 17 high bits, no shift ADDDB 100000B -- bump the sign, which carries through RBC [S]-,C1,[S] -- bounds check fault when [S] # 0, pop stack Recent Changes 23 Aug 84 definition fixes to BNDCK & RBC ... to fix up carelessness. 22 Aug 84 RBC added ... due to interesting uses in arithmetic changes and other special bounds checking. 21 Aug 84 Cleanup pass ... to fix bugs in descriptions. Arithmetic precision changes were added. MUL & DIV -> MUL, UMUL, RDIV, MDIV, UDIV ... since we think we need signed & unsigned versions of these operations. The difference between RDIV and MDIV is subtle (based on sign of remainder), and may not be in the final machine. 24 Apr 84 Added timing estimates ... to aid in choice of instructions when hand coding. 6 Apr 84 Added MUL & DIV ... as place holders for the eventual instructions. The current assumption is that they will perform complete signed multiply & divide. Added DJ & ASL ... to make the instruction set more complete. DJ is useful for filling up trap vectors and other long transfers. ASL is useful for cutting back the stack to a known value relative to L, which we do in exiting a block with extra stuff on the stack. ARL -> AL ... to make the names a little more consistent. 21 Mar 84 Stack underflow trap added ... by arrangement between McCreight and Atkinson. This makes stack save/restore much easier to code (and faster as well). 16 Mar 84 SPR => SEUR & SIFUR, LPR => LEUR, LIFUR ... at the the request of the IFU designers. Notice that this reverses a decision taken on 27 Feb 84. All instructions use identical decoding of Alpha, so EU registers and IFU registers share the same encoding space (see the declaration of ProcessorRegister in DragOpsCross). 15 Mar 84 REC dumped ... since it was largely useless. 9 Mar 84 0-byte instructions dumped ... since the IFU no longer needed them. This lets us determine the instruction length based on the top 3 bits of the opcode. 6 Mar 84 LILDB dumped ... since it complicated the IFU and is not likely to be a very high frequency instruction. CST changed to OB format ... to simplify the IFU. This was made possible by an IFU change that allows [S-2] to be easily addressable. 1 Mar 84 IN & OUT replace MAP ... Alpha no longer designates the operation. These operations perform read & write operations with cache bypassing (I think). 27 Feb 84 LIFUR & LEUR => LPR, SIFUR & SEUR => SPR ... the location of the register is given by Alpha, not the opcode. The registers of interest are described under LPR. RL => L ... which is in better agreement with S as a name. RLADD & RLSUB added ... to support Lisp (& maybe Smalltalk) arithmetic. A new trap has been added for List NaN. 21 Feb 84 Write Protect fault added ... so we could distiguish it from page fault. RIF dumped ... since it only had a 1-byte advantage over two read instructions. 10 Feb 84 Code generation samples ... were added. 7 Feb 84 Field Decsriptor mask field widened To help with boundary conditions in generating field descriptors on the fly, the mask field of FieldDescriptor was widened to include 32. This also makes it follow the same convention as the shift field. We may wish to revisit both decisions when we see more cases. NILCK dumped NILCK is used to check for NIL pointers before they are dereferenced. We do not anticipate using NILCK often enough to warrant its inclusion. In cases where we would use it, inserting an extra fetch through the pointer will be quite sufficient. We can even afford to keep all of the low 64K of virtual memory unmapped to further reduce this problem. SHL & SHR Two useful shift operations, SHL and SHR, have been introduced to replace frequently occuring cases of FSDB followed by RFU. 6 Feb 84 SFCI replaces SFCB SFCI replaces SCFB to save a byte, which increases the possible number of interfaces that can be called from a given global frame, since we can have 4 bytes of fetching preceding the SFCI. This allows us to dump RIF if it becomes necessary. RRX replaces RFX Simple name change. LCn replaces LIn LCn now allows short access to the first 8 constants. LCn replaces LIn, which was limited to the first 5 constants. LRRB bytes swapped For more commonality with instructions that added AlphaZ before fetching (Curry's suggestion). AND, OR, and XOR dumped They are not used often enough to warrant separate instructions. RAND, ROR, and RXOR should be used instead. Field Unit instructions changed (again) The Field Unit instructions have become FSDB (Field Setup Double Byte) and RFU (Register Field Unit). The previous instructions (FUDB, FUI, RFUI) are eliminated. FSDB and RFU are sufficient to do everything we need, although they are not always the most compact or efficient means to do so. We may identify special cases later in the design. 3 Feb 84 EU register names (Field, MQ) The old name Q is now Field; ICAND is now MQ. Field Unit instructions changed The Field Unit is now accessible to 3 instructions: FUDB, FUI, RFUI. These instructions all take two words of data, and take the field descriptor from either AlphaBeta or Field, and produce one word of output. Copyright c 1984 by Xerox Corporation. All rights reserved. 000 => 1 byte [000B..037B] (1 byte XOPs) 001 => 5 bytes [040B..077B] OQB format 01x => 1 byte [100B..177B] OI, LR formats 10x => 2 bytes [200B..277B] OB, LRB formats 11x => 3 bytes [300B..377B] RR, RJB, ODB, JDB, LRRB formats reserved bits, not currently used, but must be 0s governs choice of background and low bits of mask mask gives # of left-justified 1s in the mask (mask = 0 => no 1s, mask = 32 => all 1s) gives # of bits to left-shift the double word The shifter output has the input double word shifted left by fd.shift bits The default mask has fd.mask 1s right-justified in the word fd.insert => clear rightmost fd.shift bits of the mask 1 bits in the mask select the shifter output fd.insert => 0 bits in the mask select bits from Right to OR in to the result Definitions used from DragOpsCrossUtils This procedure shifts two Dragon words left by dist bits and returns the leftmost word. << code omitted >> This procedure shifts one Dragon word left by dist bits and returns the shifted word. << code omitted >> This procedure shifts one Dragon word right by dist bits and returns the shifted word. << code omitted >> This procedure is a 32-bit AND << code omitted >> This procedure is a 32-bit OR << code omitted >> This procedure is a 32-bit NOT << code omitted >> Generates Assume u,v,w are in locals Lu,Lv,Lw Assume AddFunny to be called via DFC Generates Extend 32-bit signed number on stack to 64-bit signed number on stack {3 cycles, 7 bytes} Narrow 64-bit signed number on stack to 32-bit signed number on stack {4 cycles, 10 bytes} Extend 16-bit signed number on stack to 32-bit signed number on stack {4 cycles, 12 bytes} Narrow 32-bit signed number on stack to 16-bit signed number on stack {4 cycles, 10 bytes} BpStyleDefBeginStyle (Cedar) AttachStyle (root) "format for root nodes" { docStandard .5 in topMargin .8 in headerMargin 0.5 in footerMargin 0.5 in bottomMargin 1.0 in rightMargin 1.0 in leftMargin 6.5 in lineLength 24 pt topIndent 24 pt topLeading 0 leftIndent 0 rightIndent } StyleRule EndStyle 86.5 in lineLength 1.0 in leftMargin 1.0 in rightMarginIcenterMark centerHeaderbImemoHeads*L&L 'IlogoIabstract t! 0iNoxItitleN m1> S +S0SFF S &SS88 S0 S S D8( S1 ci NSHS Icode  * 10 sp tabStopsT10 sp tabStopsT10 sp tabStops T10 sp tabStops T10 sp tabStops T10 sp tabStops  T  * 10 sp tabStopsT10 sp tabStopsT10 sp tabStops T10 sp tabStops T10 sp tabStops T10 sp tabStops   9 sp tabStopsT 9 sp tabStops  * 10 sp tabStopsT10 sp tabStopsT10 sp tabStops T10 sp tabStops T10 sp tabStops T10 sp tabStops  S2 QS SSSS ( T . 10 sp tabStopsT10 sp tabStopsT10 sp tabStops T10 sp tabStops T10 sp tabStops T10 sp tabStops P R SSZS* R S  S+  S$ S,S12 S**  S55  S<>  S77 S  S S  S  S R Sz (S SM  S11S  S22S SW  S..S  S//S R$ +IitemWWU-UU1UU&U*fifU*f *UU R R zWBR  S1.5 in tabStops U1.5 in tabStops U1.5 in tabStops U1.5 in tabStops U1.5 in tabStops1U1.5 in tabStops U1.5 in tabStops U1.5 in tabStopsU1.5 in tabStopsU1.5 in tabStops/U1.5 in tabStops  )U1.5 in tabStops U1.5 in tabStopsR 6U:URtRR R  VU20 sp tabStops +U20 sp tabStops$*U20 sp tabStops'-U20 sp tabStops)/U20 sp tabStops9?  SN S,,P Rkk Sz(S" S f- S7 S S S S SP R S$ c K  S S S; S\) S SP R biJ 3J$J$J  224 sp tabStopsJ24 sp tabStops11 24 sp tabStops T24 sp tabStops1124 sp tabStops24 sp tabStops-J24 sp tabStops(24 sp tabStopsJ24 sp tabStops--JJ n)M ;;TJJ 88T;;   3LT77 T,,  2CTMMTTTT''JJ! BWWJJJJ  AUUJJJJ  AVVJJJ  3JJJ  2JJJ  1JJP Q8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlueTQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGluebfsTQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGluefsos(8TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue 0TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue$4TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue(8TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue!iosaTQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue 0TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlueTQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue(TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue!1TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlueTQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue9TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue"2TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue1ATQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue"2TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue)TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue(TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue*TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue/TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue#TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue'TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue(TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue 0TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue,TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue"TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlueBRTQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue-TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlueBTQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue*TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue)9TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue"2TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue!TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue"2TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlueCSTQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue,TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue!TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue/TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue/TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue&TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue&TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue&TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue&TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue&TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue%TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue/?TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue/?TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue-TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue!TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue*TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue)9TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue)TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue)TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlueTQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlueTQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue&TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue'TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue#TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue.TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue 0TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue&TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue*TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue(8TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue$4TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue"2TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue*TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue-TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue*TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue)9TQ8 pt leading 10 pt 10 pt 10 pt bottomLeadingGlue 10 pt 10 pt 10 pt topLeadingGlue/P  R  18 sp tabStops%%T18 sp tabStopsc4AT18 sp tabStopsT18 sp tabStops T18 sp tabStops 18 sp tabStops 5?T18 sp tabStops%.T18 sp tabStops 3BT18 sp tabStops $T18 sp tabStops ,T18 sp tabStops-2T18 sp tabStops!T18 sp tabStops $2T18 sp tabStops *:T18 sp tabStops.9T18 sp tabStops %4T18 sp tabStops 18 sp tabStops 5?T18 sp tabStops%.T18 sp tabStops 3BT18 sp tabStops $T18 sp tabStops ,T18 sp tabStops-3T18 sp tabStops ,T18 sp tabStops!T18 sp tabStops $2T18 sp tabStops (7T18 sp tabStops#T18 sp tabStops.9T18 sp tabStops &5T18 sp tabStopsT18 sp tabStops  18 sp tabStops +T18 sp tabStops T18 sp tabStops T18 sp tabStops T18 sp tabStops 18 sp tabStops T18 sp tabStopsT18 sp tabStopsck!T18 sp tabStops T18 sp tabStops T18 sp tabStops T18 sp tabStopsT18 sp tabStops 18 sp tabStopsT18 sp tabStops##T18 sp tabStops$$ 18 sp tabStops T18 sp tabStops T18 sp tabStops T18 sp tabStops T18 sp tabStops T18 sp tabStops RR 1.35 in tabStopsYT1.35 in tabStops"&T1.35 in tabStops/BT1.35 in tabStops 8IT1.35 in tabStops 1.35 in tabStopsZT1.35 in tabStops:OT1.35 in tabStops)>T1.35 in tabStops -=T1.35 in tabStops$T1.35 in tabStops 1.35 in tabStopsZT1.35 in tabStops,T1.35 in tabStops-T1.35 in tabStops(5T1.35 in tabStops-T1.35 in tabStops 1.35 in tabStopsZT1.35 in tabStopsT1.35 in tabStops %4T1.35 in tabStops '5T1.35 in tabStops -=T18 sp tabStopsP  R  RTT  RJJ (RcM  R66  R R0B  R//  R{{  'R   R!!  R~~   R[[ Rmm   R  (Rsw R22 R\\  R..  RDD  R  #R  RD  R ? |  R  R R4 -t R^^ RBm 'R(4  R.. R4: