.TITLE ASSMBL .IDENT "V1.1" ; ; Author: D. Mischler 4-JUN-88 ; ; This module is called to assemble an instruction ; into memory. The opcode table is required. ; ; ; Addressing mode definitions. ; M.DFER = 10 ; Deferred address bit. M.REG = 00 ; Register mode. M.AINC = 20 ; Auto-increment mode. M.ADEC = 40 ; Auto-decrement mode. M.INDX = 60 ; Indexed mode. .PSECT DATA,D,RW ; ; Local data. ; ERRPTR: .BLKW 1 ; Pointer to text in error. INSADR: .BLKW 1 ; Instruction address. INSWRD: .BLKW 1 ; Instruction opcode word. .PSECT RODATA,D,RO ; ; Opcode class dispatch table. ; CLSTBL: .WORD BRANCH ; 0 - Branch instructions. .WORD COND ; 1 - Condition code instructions. .WORD DOUBLE ; 2 - Double operand instructions. .WORD IMMED ; 3 - 3-bit immediate instructions. .WORD FPADST ; 4 - Floating point accumulator destination. .WORD FPASRC ; 5 - Floating point accumulator source. .WORD IMMED ; 6 - 6-bit immediate instructions. .WORD NONE ; 7 - No operands. .WORD IMMED ; 10 - 8-bit immediate instructions. .WORD REG ; 11 - Single register operand. .WORD REGDST ; 12 - Register destination with any source. .WORD REGSRC ; 13 - Register source with any destination. .WORD SINGLE ; 14 - Single operand. .WORD SOB ; 15 - Subtract one and branch instruction. .WORD ERRXIT ; 16 - Illegal class. .WORD ERRXIT ; 17 - Illegal class. ; ; Table of condition code characters and bit assignments. ; CCRTBL: .BYTE 'N,10 ; N (negative) bit. .BYTE 'Z,4 ; Z (zero) bit. .BYTE 'V,2 ; V (overflow) bit. .BYTE 'C,1 ; C (carry) bit. CCRLEN = <.-CCRTBL>/2 .PAGE .PSECT CODE,I,RO ; ; Instruction assembler. ; On entry: R0 points to instruction text, R5 contains address. ; On exit: R0 and R5 updated. ; ASSMBL:: MOV R0,ERRPTR ; Save opcode text address. MOV R5,INSADR ; Save instruction address. CALL CKSPCL ; Is this opcode a special case? BCS 20$ ; Yes, do not look it up in opcode table. CALL U$SYMN ; Convert opcode name into RAD50, OK? BCS ERRXIT ; No, complain. MOV #E.ILOP,R1 ; Point to illegal opcode message. MOV #OPCTBL,R4 ; Point to start of opcode table. 10$: CMP R2,OP.MNE(R4) ; Does first word of mnemonic match? BNE 30$ ; No, try next table entry. CMP R3,OP.MNE+2(R4) ; How about the second word? BNE 30$ ; No, try next entry. ; Dispatch on instruction class. 20$: MOV OP.VAL(R4),R1 ; Get instruction opcode base value. MOV R1,INSWRD ; Save it for later. CALL WRITE ; Write it to the instruction stream, OK? BCS ERRXIT ; No, complain. MOV (R4),R2 ; Get opcode class. SWAB R2 ; Put class in low byte. ASH #-3,R2 ; Position it for indexing. BIC #^C<36>,R2 ; Mask off garbage. JMP @CLSTBL(R2) ; Dispatch by instruction class. ; Try next opcode table entry. 30$: ADD #OP.LEN,R4 ; Point to next opcode table entry. TST (R4) ; End of table? BNE 10$ ; No, keep looking. ; Error exit point. ERRXIT: MOV ERRPTR,R0 ; Recover address of text in error. SEC ; Make sure error bit is set. NONE: RETURN .PAGE ; ; Handle branch instructions. ; BRANCH: CALL OPRCHK ; Is there an operand? BCS ERRXIT ; No, complain. CALL XPRESS ; Evaluate branch target address, OK? BCS ERRXIT ; No, complain. SUB R5,R1 ; Subtract current "PC" from target. ASR R1 ; Convert byte offset to word offset. MOVB R1,R2 ; Make a sign-extended copy of low byte. CMP R1,R2 ; Is branch target within range? BNE BR2FAR ; No, complain. BISB R1,INSWRD ; Stuff offset into branch instruction. CALL INSWRT ; Write instruction word, OK? BCS ERRXIT ; No, complain. RETURN ; Branch is out of range. BR2FAR: MOV #E.2FAR,R1 ; Get error message address. BR ERRXIT ; Take error exit. FPADST: ; 4 - Floating point accumulator destination. FPASRC: ; 5 - Floating point accumulator source. MOV #E.ILOP,R1 ; Disallow floating point instructions for now. BR ERRXIT ; ; Handle instructions with two general operands. ; DOUBLE: CALL OPRAND ; Process general operand, OK? BCS ERRXIT ; No, complain. ASH #6,R1 ; Position mode for source operand. BIS R1,INSWRD ; Update instruction word with source mode. ; ; Handle instructions with a single general operand. ; SINGLE: CALL OPRAND ; Process general operand, OK? BCS ERRXIT ; No, complain. BIS R1,INSWRD ; Update instruction word with destination mode. CALLR INSWRT ; Rewrite instruction word and exit. ; ; Take care of special-purpose immediate mode instructions. ; IMMED: CALL OPRCHK ; Is there an operand? BCS ERRXIT ; No, complain. CALL XPRESS ; Evaluate immediate operand, OK? BCS ERRXIT ; No, complain. MOV (R4),R2 ; Get opcode class word. BIC #170000,R2 ; Remove class bits. COM R2 ; Invert immediate data mask. BIC R2,R1 ; Mask immediate operand to correct width. BIS R1,INSWRD ; Update instruction word. CALLR INSWRT ; Rewrite instruction word and exit. ; ; Handle instructions that take a single register argument. ; REG: CALL OPRCHK ; Is there an operand? BCS ERRXIT ; No, complain. CALL REGSTR ; Get register number, OK? BCS ERRXIT ; No, complain. BIS R1,INSWRD ; Update instruction word. CALLR INSWRT ; Rewrite instruction word and exit. ; ; Handle instructions that take any mode for source, ; but only a register for a destination. ; REGDST: CALL OPRAND ; Process general operand, OK? BCS ERRXIT ; No, complain. BIS R1,INSWRD ; Update instruction word with source mode. CALL OPRCHK ; Is there another operand? BCS ERRXIT ; No, complain. CALL REGSTR ; Get register number, OK? BCS ERRXIT ; No, complain. ASH #6,R1 ; Put register number in position. BIS R1,INSWRD ; Update instruction word with register. CALLR INSWRT ; Rewrite instruction word and exit. ; ; Assemble an SOB instruction. ; SOB: CALL OPRCHK ; Is there an operand? BCS ERRXIT ; No, complain. CALL REGSTR ; Get register number, OK? BCS ERRXIT ; No, complain. ASH #6,R1 ; Position register number correctly. BIS R1,INSWRD ; Update instruction word. CALL OPRCHK ; Is there another operand? BCS ERRXIT ; No, complain. CALL XPRESS ; Evaluate branch target address, OK? BCS ERRXIT ; No, complain. NEG R1 ; Negate target address. ADD R5,R1 ; Produce negative byte offset. ASR R1 ; Convert byte offset to word offset. CMP R1,#77 ; Is target within range? BHI BR2FAR ; No, complain. BISB R1,INSWRD ; Stuff offset into branch instruction. CALL INSWRT ; Write instruction word, OK? BCS ERRXIT ; No, complain. RETURN ; ; Handle instructions with a register source operand. ; REGSRC: CALL OPRCHK ; Is there an operand? BCS ERRXIT ; No, complain. CALL REGSTR ; Get register number, OK? BCS ERRXIT ; No, complain. ASH #6,R1 ; Position register number correctly. BIS R1,INSWRD ; Update instruction word. CALL OPRAND ; Process general operand, OK? BCS ERRXIT ; No, complain. BIS R1,INSWRD ; Update instruction word with destination mode. CALLR INSWRT ; Rewrite instruction word and exit. ; ; Routine to handle condition code operations. ; COND: MOV #CCRTBL,R1 ; Point to start of condition code table. MOV #CCRLEN,R2 ; Get number of table entries. 10$: CMPB (R0),(R1) ; Does condition flag match table entry? BNE 20$ ; No, try next entry. BISB 1(R1),INSWRD ; Update instruction word. INC R0 ; Point to next condition flag (or terminator). BR COND ; Try next flag. ; Condition flag doesn't match table entry. 20$: TST (R1)+ ; Point to next table entry. SOB R2,10$ ; Try all entries. CALLR INSWRT ; Write instruction word to target task. .PAGE ; ; Routine to check an opcode for special case dispatching. ; On entry: R0 points to opcode mnemonic. ; On exit: Carry set if special dispatching needed, R4 points ; to opcode table entry for dispatching. ; CKSPCL: MOVB 1(R0),R1 ; Get second character of mnemonic. SWAB R1 ; Put in high byte. BISB (R0),R1 ; Pack first character in with it. MOV #SEOPC,R4 ; Point to SEx opcode entry. CMP #"SE,R1 ; Set condition operation? BEQ 20$ ; Yes, force special dispatch. MOV #CLOPC,R4 ; Point to CLx opcode entry. CMP #"CL,R1 ; Clear condition operation? BNE 10$ ; No, dispatch normally. CMPB #'R,2(R0) ; Is operation actually CLRx? BNE 20$ ; No, force special dispatch. 10$: CLC ; Indicate normal dispatch is needed. RETURN ; Here to force special dispatch. 20$: ADD #2,R0 ; Point past constant mnemonic. SEC ; Indicate special dispatch is needed. RETURN ; ; Routine to write the instruction word to the target task. ; INSWRT: MOV R5,-(SP) ; Preserve instruction stream address. MOV INSADR,R5 ; Get instruction word address. MOV INSWRD,R1 ; Get instruction word contents. CALL WRITE ; Write it to the target task. MOV (SP)+,R5 ; Recover instruction stream address. RETURN .PAGE ; ; Routine to process a general operand. ; On entry: R0 points to delimiter preceding operand. ; On exit: R1 contains mode and register, or carry set if error. ; OPRAND: CALL OPRCHK ; Is there likely to be an operand? BCS 30$ ; No, complain. CLR R4 ; Initialize mode and register to zeroes. CMPB #'@,(R0) ; Is operand deferred? BNE 10$ ; No, skip next section. INC R0 ; Skip over '@. BIS #M.DFER,R4 ; Remember operand is deferred. 10$: CMPB #'#,(R0) ; Is operand immediate? BEQ OPRIMM ; Yes, take care of immediate operand. CALL REGSTR ; Is operand just a register? BCC 20$ ; Yes, finish up and exit. MOV R0,ERRPTR ; Save error text address. CALL XPRESS ; Attempt to evaluate expression, OK? BCC OPRIDX ; Yes, take care of indexed mode. MOV ERRPTR,R0 ; Recover error text address. ; Operand mode is register indirect, auto-increment, or auto-decrement. CMPB #'-,(R0)+ ; Is mode auto-decrement? BEQ 16$ ; Yes, take care of it. DEC R0 ; Back up over the '- that isn't there. CALL PRGSTR ; Get register number, OK? BCS 30$ ; No, we have a problem. BIS #M.AINC,R4 ; Assume mode is auto-increment. CMPB #'+,(R0)+ ; Is mode auto-increment? BEQ 20$ ; Yes, finish up. DEC R0 ; Back up over the '+ that isn't there. BIT #M.DFER,R4 ; Is operand deferred twice? BNE 15$ ; Yes, this is getting a little messy. MOV #M.REG!M.DFER,R4; Mode is register deferred. BR 20$ ; Finish up and exit. ; Use indexed mode with 0 offset for double indirection. 15$: BIS #M.INDX!M.DFER,R1 ; Set appropriate addressing mode. MOV R1,R4 ; Save data for later. CLR R1 ; Make a zero. CALL WRITE ; Write zero offset word. BR 20$ ; Finish up. ; Mode is auto-decrement. 16$: CALL PRGSTR ; Get register number, OK? BCS 30$ ; No, we have a problem. BIS #M.ADEC,R4 ; Set up addressing mode. ; Finish up for register direct, deferred, auto-increment and auto-decrement. 20$: BIS R4,R1 ; Put mode and register info together. CLC 30$: RETURN .PAGE ; ; General operand is indexed. ; OPRIDX: CMPB #'(,(R0) ; Was an index register specified? BNE 20$ ; No, assume relative mode. BIS #M.INDX,R4 ; Set indexed mode. CALL WRITE ; Write displacement, OK? BCS 10$ ; No, complain. CALL PRGSTR ; Get register number, OK? BCS 10$ ; No, complain. BIS R4,R1 ; Set up mode and register for exit. 10$: RETURN ; Relative mode operand. 20$: BIS #M.INDX+7,R4 ; Set relative mode. SUB R5,R1 ; Calculate offset from PC to target. SUB #2,R1 ; Account for offset word length. CALL WRITE ; Write offset to target task, OK? BCS 30$ ; No, complain. MOV R4,R1 ; Set mode and register for exit. 30$: RETURN ; ; General operand is immediate. ; OPRIMM: BIS #M.AINC+7,R4 ; Set mode and register. INC R0 ; Skip over pound sign. CALL XPRESS ; Evaluate immediate value, OK? BCS 10$ ; No, complain. CALL WRITE ; Write immediate value, OK? BCS 10$ ; No, complain. MOV R4,R1 ; Get mode and register for exit. 10$: RETURN ; ; Routine to check for an operand. ; On entry: R0 points to delimiter. ; OPRCHK: CMPB #' ,(R0) ; Is delimiter a space? BEQ 10$ ; Yes, it's probably OK. CMPB #',,(R0) ; Is delimiter a comma? BNE 20$ ; No, we have a problem. 10$: INC R0 ; Point past delimiter. MOV R0,ERRPTR ; Update error text pointer. RETURN ; Delimiter is not correct. 20$: MOV #E.IOMO,R1 ; Indicate an illegal or missing operand. SEC ; Make sure complaint bit is set. RETURN .PAGE ; ; Routine to check a parenthesized register specification. ; PRGSTR: CMPB #'(,(R0)+ ; Open parenthesis? BNE 10$ ; No, we have a problem. CALL REGSTR ; Get register number, OK? BCS 20$ ; No, complain. CMPB #'),(R0)+ ; Is register terminated properly? BEQ 20$ ; Yes, exit quietly. 10$: MOV #E.ILRN,R1 ; Point to error message. SEC ; Set complaint bit. 20$: RETURN ; ; Routine to check for a register name. ; On entry: R0 points to name. ; On exit: R1 contains register number and R0 updated, ; or carry set if not a register. ; REGSTR: MOVB 1(R0),R2 ; Get second byte of possible register. SWAB R2 ; Put it in the high byte. BISB (R0),R2 ; Put register name together. MOV #REGTBL,R1 ; Point to register name table. 10$: CMP R2,(R1) ; Found a match? BEQ 20$ ; Yes, return register number. TST (R1)+ ; Hit end of table? BNE 10$ ; No, keep looking. MOV #E.ILRN,R1 ; Point to appropriate error message. SEC ; Indicate name is not a register. RETURN ; Found register name. 20$: ADD #2,R0 ; Point past register name. SUB #REGTBL,R1 ; Get word offset to name in table. ASR R1 ; Get actual register number. RETURN ; ; Routine to write a word to target task instruction space. ; On entry: R1 contains value, R5 contains address. ; On exit: R5 updated, or carry set and R1 contains error pointer. ; WRITE: CALL M$WI5 ; Write word to target task, OK? BCS 10$ ; No, get error message address. INC R5 ; Update target task address. INC R5 RETURN ; Here if write failed. 10$: MOV #E.MWF,R1 ; Point to error message. RETURN .END