page external references and definitions opt d include symbols opt -c don't show all dc.b bytes opt -t don't give symbol table opt x don't list cross reference xref GetValue,GetLine,GetByte,GetNonSpace,GetSymbol xref Match_Sym,CommonErr,Upper_case,back_up,add_sym xref writs,Out_Char_A,writb,Err_char,Dis_one xref Save_place,Restore_ln,CRLF xref azm_address,output_buff,Sym_name,Prompt_len xdef asm_oneline page equates tab equ $09 LF equ $0A CR equ $0D space equ $20 opbufflen equ 6 max. chars in opcode (must be even) * One of these values is kept in operand_len Byte_len equ $0 Word_len equ $1 Long_len equ $2 Short_len equ $3 No_len equ $4 (when one isn't given) * The valid EA bit field is arranged by bit like this: * * 15 14 13 12 11 10 9 8 7 6 5 4 * * +--+--+----+-----+-----+-----+--------+-----+-----+-----+--------+---+ * * |Dn|An|(An)|(An)+|-(An)|d(An)|d(An,Xi)|Abs.W|Abs.L|d(PC)|d(PC,Xi)|Imm| * * +--+--+----+-----+-----+-----+--------+-----+-----+-----+--------+---+ * * 3 2 1 0 * * +----+----+----+-------+ * * | SR | CCR| USP|REGLIST| * * +----+----+----+-------+ * * A 1 bit at a bit location indicates that the addressing mode for that * * bit is valid for the particular instruction. * DATA_REG equ $8000 ADDR_REG equ $4000 INDIRECT equ $2000 POSTINC equ $1000 PREDEC equ $0800 INDRDISP equ $0400 INDRINDXDIS equ $0200 ABSSHORT equ $0100 ABSLONG equ $0080 PCDISP equ $0040 PCINDXDIS equ $0020 IMMEDIATE equ $0010 SR_REG equ $0008 CCR_REG equ $0004 USP_REG equ $0002 REG_LIST equ $0001 No_EA equ 0 page asm_oneline sect PromProg put it in EPROM * This subroutine is called to read one line of text and assemble it * at the address (azm_address). * On return d0.b = 0 if the line was blank otherwise do.b <> 0. * To start we read a line of text. * First check for a label azm_prompt dc.b 'A*>',0 assembler prompt azm_prlen equ 3 length of prompt asm_oneline lea azm_prompt,a0 bsr writs print prompt move.w #azm_prlen,Prompt_len bsr GetLine get line to assemble bsr GetByte get first byte of line cmp.b #space,d0 if first char is a space or beq.s azm_opcode ...a tab, there is no label cmp.b #tab,d0 beq.s azm_opcode cmp.b #CR,d0 beq assem_exit bsr Back_up put back first char of name bsr GetSymbol get label in buffer bsr GetNonSpace advance to first char of opcode bsr Back_up bsr Match_Sym see if it already exists bcc.s no_match move.l (a1),d0 cmp.l azm_address,d0 label is defined; see if it conflicts bne symconflict bra.s azm_opcode no_match bsr Add_sym establish label and its value move.l azm_address,(a0) * Read in the next few chars into the opcode mnemonic buffer azm_opcode lea op_buff,a0 movea.l a0,a1 make a copy moveq #opbufflen-1,d1 fill_op move.b #' ',(a1)+ fill opcode buffer with spaces dbf d1,fill_op moveq #opbufflen-1,d1 # bytes in opcode buffer oploop bsr GetByte get byte of opcode bsr Upper_case convert to uppercase cmp.b #'A',d0 bcs.s opdone cmp.b #'Z',d0 bhi.s opdone move.b d0,(a0)+ dbf d1,oploop bra bad_opcode opcode too long if we fell through * We have read in the mnemonic. See if the mnemonic appears in the table. opdone bsr Back_up put back last char we fetched lea op_table,a1 oplookup tst.w (a1) see if it is end of table beq bad_opcode moveq #opbufflen/2-1,d1 lea op_buff,a0 cmp_loop cmp.w (a0)+,(a1)+ see if this entry matches dbne d1,cmp_loop beq.s op_found * We didn't match. Advance table pointer to next entry and try again add.w d1,d1 double it (because 2 bytes per loop) lea $8(a1,d1.w),a1 point to start of next entry bra oplookup * We have found the mnemonic in the table. * Save the pointer to the table and continue processing the line. * First check to see if a operand length (.B/L/W) is given. op_found move.l a1,table_ptr bsr GetByte get next byte off line cmp.b #'.',d0 beq.s oplen_given move.b #No_len,operand_len bsr Back_up put back char bra azm_oprands oplen_given bsr GetByte bsr Encode_len find operation length move.b d0,operand_len * We now have length of operation. * See if there is more to assemble. azm_oprands move.w #No_EA,src_type default value move.w #No_EA,dst_type default value bsr GetNonSpace cmp.b #CR,d0 beq AZM_it assemble if end of line * assemble first (only?) operand bsr Back_up put back non-CR character bsr azm_EA get source EA move.w EA_type,src_type type move.l EA_ext,src_ext extension word (if any) move.b EA_field,src_field mode/reg field * We have the first operand. * Check if there is a second bsr GetNonSpace cmp.b #CR,d0 end of line? beq AZM_it cmp.b #',',d0 a comma always separates operands bne unknown bsr azm_EA get destination EA move.w EA_type,dst_type type move.l EA_ext,dst_ext extension word (if any) move.b EA_field,dst_field mode/reg field * We should either see the end of line or a separator and a comment. bsr GetByte cmp.b #space,d0 beq.s AZM_it cmp.b #CR,d0 beq.s AZM_it cmp.b #tab,d0 bne unknown * At this point we have assembled the parts of the line. * Now we must check if they operands/mnemonic/length combination is legal. * If it is legal we must then construct the binary. AZM_it move.l table_ptr,a0 recall pointer to table move.l (a0)+,d7 get opcode parameter move.l (a0),a0 get address of assembling routine jsr (a0) go to it moveq #-1,d0 indicate we assembled something rts assem_exit clr.b d0 indicate we assembled nothing rts page subroutines ****************************************************************************** * * ENTRY: D0.b contains an ASCII character * EXIT : D0.b contains an encoding of this byte: * 'B', 'b' ---> 00 * 'W', 'w' ---> 01 * 'L', 'l' ---> 10 * 'S', 's' ---> 11 * * If the byte isn't one of these four a jump is made to an error routine. * ****************************************************************************** Encode_len jsr upper_case cmp.b #'B',d0 bne.s notBlen moveq #byte_len,d0 rts notBlen cmp.b #'W',d0 bne.s notWlen moveq #word_len,d0 rts notWlen cmp.b #'L',d0 bne.s notLlen moveq #long_len,d0 rts notLlen cmp.b #'S',d0 bne oplen_error moveq #short_len,d0 rts ****************************************************************************** * * This routine will read the next two characters and return in D0.b * an encoded value for the register specified. * D0 -> 0, D1 -> 1, ... D7 -> 7, A0 -> 8, A1 -> 9, ... A7 -> 15, * PC -> 16, SR -> 17, CCR -> 18, USP -> 19, other -> 20 * SP is a synonym for A7. * * This is really ugly. * * Check_reg is the same but forces an error if it is not a legit register * ****************************************************************************** Check_reg bsr Encode_reg cmp.b #20,d0 see if it is "other" register beq regerr Check_exit rts Encode_reg movem.l d1/a0,-(sp) jsr GetSymbol lea Sym_name,a0 move.w (a0)+,d0 get (length of symbol)/2 cmp.b #2,d0 CCR/USP? beq ccr_usp cmp.b #1,d0 SR, PC, D0, D1, etc? bne ER_exit moveq #16,d0 cmp.w #$5043,(a0) "PC" beq.s Encreg_exit moveq #17,d0 cmp.w #$5352,(a0) "SR" beq.s Encreg_exit moveq #15,d0 cmp.w #$5350,(a0) "SP" beq.s Encreg_exit cmp.b #'D',(a0) Dx? beq.s shouldbe_dx cmp.b #'A',(a0) Ax? bne.s ER_exit move.b $1(a0),d0 sub.b #'0',d0 see if proper range bcs.s ER_exit cmp.b #8,d0 bcc.s ER_exit add.b #8,d0 a0 -> 8, a1 -> 9, ..., a7 -> 15 bra.s Encreg_exit ccr_usp moveq #18,d0 PC -> 18 cmp.l #$43435200,(a0) "CCR",0 beq.s Encreg_exit moveq #19,d0 cmp.l #$55535000,(a0) "USP",0 bne.s ER_exit bra.s Encreg_exit shouldbe_dx move.b $1(a0),d0 sub.b #'0',d0 see if proper range bcs.s ER_exit cmp.b #8,d0 bcc.s ER_exit Encreg_exit movem.l (sp)+,d1/a0 rts ER_exit movem.l (sp)+,d1/a0 move.b #20,d0 not one of the above rts *************************************************************************** * Entry: basic opcode in d0 * Also : EA field in src_field. * Does : merges dst_field in with opcode in d0 and assembles it in. * It then assembles any necessary extension words. *************************************************************************** Stndrd_sea and.b #$C0,d0 clear out lowest 6 bits or.b src_field,d0 bsr opcode_d0 assemble in opcode bsr stndrd_sext assemble any necessary extension word(s) rts *************************************************************************** * Entry: EA type src_type * Does: forms extension words as necessary *************************************************************************** Stndrd_sext movem.l d0-d1,-(sp) move.w src_type,d1 move.l src_ext,d0 and.w #$F80C,d1 just return if this mode doesn't bne.s SSext_exit require an extension word move.w src_type,d1 btst #7,d1 bne SSext_long btst #4,d1 bne.s SSext_imm * If not one of the above then it must be word SSext_word bsr opcode_d0 bra.s SSext_exit SSext_long swap d0 save 16 ms bits bsr opcode_d0 swap d0 bsr opcode_d0 bra.s SSext_exit SSext_imm cmp.b #long_len,operand_len beq.s SSext_long cmp.b #word_len,operand_len beq.s SSext_word bsr opcode_d0 save 16 bits (although upper 8 are 0) SSext_exit movem.l (sp)+,d0-d1 rts *************************************************************************** * Entry: opcode in d0.w * Also : EA field in src_field. * Does : merges dst_field in with opcode in d0 and assembles it in. * It then assembles any necessary extension words. *************************************************************************** Stndrd_dea and.b #$C0,d0 clean out lowest 6 bits or.b dst_field,d0 merge EA field in 6 l.s. bits bsr opcode_d0 assemble in opcode bsr stndrd_dext assemble any necessary extension word(s) rts *************************************************************************** * Entry: EA type dst_type * Does: forms extension words as necessary *************************************************************************** Stndrd_dext movem.l d0-d1,-(sp) move.l dst_ext,d0 get full extension word move.w dst_type,d1 and.w #$F80C,d1 just return if this mode doesn't bne.s SDext_exit require an extension word move.w dst_type,d1 btst #7,d1 bne SDext_long btst #4,d1 bne.s SDext_imm * If not one of the above then it must be word SDext_word bsr opcode_d0 word extension bra.s SDext_exit SDext_long swap d0 save upper 16 bits bsr opcode_d0 swap d0 bsr opcode_d0 bra.s SDext_exit SDext_imm cmp.b #long_len,operand_len beq.s SDext_long cmp.b #word_len,operand_len beq.s SDext_word bsr opcode_d0 save 16 bits (although lower 8 are 0) SDext_exit movem.l (sp)+,d0-d1 rts ****************************************************************************** * Entry: opcode in d0.w * Size of operation in operand_len. * * Exit: opcode with size field merged in bits 6/7 in d0. ****************************************************************************** SizeBits_67 move.w d1,-(sp) cmp.b #short_len,operand_len beq Bad_size bcs.s SB67_OK if cc then NO_LEN given move.b #word_len,operand_len default value SB67_OK move.b operand_len,d1 rol.b #6,d1 and.b #$3F,d0 zap bits 6 and 7 or.b d1,d0 merge in length field move.w (sp)+,d1 rts ****************************************************************************** * This subroutine take the dst_field[2:0] bits and puts them * in the opcode [11:9] bits. ****************************************************************************** Dest_9to11 move.w d1,-(sp) move.b dst_field,d1 and.w #$7,d1 ror.w #7,d1 and.w #$F1FF,d0 blank bits [11:9] or.w d1,d0 move.w (sp)+,d1 rts ****************************************************************************** * This subroutine take the src_field[2:0] bits and puts them * in the opcode [11:9] bits. ****************************************************************************** Src_9to11 move.w d1,-(sp) move.b src_field,d1 and.w #$7,d1 ror.w #7,d1 and.w #$F1FF,d0 blank bits [11:9] or.w d1,d0 move.w (sp)+,d1 rts ****************************************************************************** * This subroutine take the src_field[2:0] bits and puts them * in the opcode [2:0] bits. ****************************************************************************** Src_0to2 move.w d1,-(sp) move.b src_field,d1 and.w #$7,d1 and.b #$F8,d0 blank bits [2:0] or.w d1,d0 move.w (sp)+,d1 rts ****************************************************************************** * This subroutine take the dst_field[2:0] bits and puts them * in the opcode [2:0] bits. ****************************************************************************** Dst_0to2 move.w d1,-(sp) move.b dst_field,d1 and.w #$7,d1 and.b #$F8,d0 blank bits [2:0] or.w d1,d0 move.w (sp)+,d1 rts ****************************************************************************** * This routine will take the src_ext[0:2] field and put it in d0[11:9]. ****************************************************************************** count_9to11 move.w d0,-(sp) move.l src_ext,d1 and.w #$7,d1 make sure we have only 3-bit field ror.w #7,d1 align field to bits [11:9] and.w #$F1FF,d0 blank bits [11:9] or.w d1,d0 merge in count field move.w (sp)+,d1 rts ****************************************************************************** * This routine make sure that the operand_len is either word or long. * No_len will be changed to word_len. ****************************************************************************** WL_only move.w d1,-(sp) cmp.b #byte_len,operand_len beq WL_lenerr cmp.b #short_len,operand_len beq bad_size cmp.b #long_len,operand_len beq.s WL_exit move.b #word_len,operand_len WL_exit move.w (sp)+,d1 rts ****************************************************************************** * This routine make sure that the operand_len is word or no_len. ****************************************************************************** W_only move.w d1,-(sp) cmp.b #word_len,operand_len beq.s W_exit cmp.b #no_len,operand_len bne WO_lenerr W_exit move.w (sp)+,d1 rts ****************************************************************************** * This routine will put a 1 in bit 8 if d0 if operand_len is size LONG. * This routine will put a 0 in bit 8 if d0 if operand_len is size WORD. * Any other operand size is considered an error. ****************************************************************************** SizeBit_WL8 move.w d1,-(sp) bsr WL_only moveq #2,d1 leave only bit 1 and.w operand_len,d1 rol.w #7,d1 put bit 1 in bit 8 position bclr #8,d0 make sure bit is erased or.w d1,d0 merge in length field move.w (sp)+,d1 rts ****************************************************************************** * This routine will take the value in src_ext and save one or two extension * words depending whether the operation is long or short. ****************************************************************************** stndrd_imm move.l d0,-(sp) move.l src_ext,d0 cmp.b #long_len,operand_len bne.s stimm_word swap d0 bsr opcode_d0 assemble in ms 16 bits swap d0 stimm_word bsr opcode_d0 assemble in ls 16 bits move.l (sp)+,d0 rts ****************************************************************************** * This routine simply puts the destination field in the opcode and saves the * opcode away. ****************************************************************************** dstEA_field and.b #$C0,d0 make sure ls 6 bits are 0 or.b dst_field,d0 bsr opcode_d0 rts ****************************************************************************** * This routine simply puts the source field in the opcode and saves the * opcode away. ****************************************************************************** srcEA_field and.b #$C0,d0 make sure ls 6 bits are 0 or.b src_field,d0 bsr opcode_d0 rts ****************************************************************************** * This field puts the word in d0 at the assembly address and advances * the assembly pointer. ****************************************************************************** opcode_d0 move.l a0,-(sp) move.l azm_address,a0 move.w d0,(a0)+ move.l a0,azm_address move.l (sp)+,a0 rts ****************************************************************************** * This routine checks that the source is not An with a operation length * of "byte." ****************************************************************************** Src_A_byte cmp.b #byte_len,operand_len bne.s SAB_exit cmp.w #ADDR_REG,src_type beq WL_lenerr SAB_exit rts ****************************************************************************** * This routine will take the value in src_ext, which is assumed to be * a 3-bit value, and put it in bits [11:9] of d0. ****************************************************************************** QData move.w d1,-(sp) move.l src_ext,d1 get whole value and.w #$7,d1 get just the bits we want. Note 8 -> 0 ror.w #7,d1 align to 9:11 field and.w #$F1FF,d0 make sure field is 0 or.w d1,d0 move.w (sp)+,d1 rts ****************************************************************************** * This subroutine scans the line and builds the MOVEM register bitmap. * Each register in the list is represented by a "1" in the position * corresponding to the register name in this map: * Bit# 15 14 13 12 11 10 9 8 7 6 5 4 3 2 1 0 * +--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+ * |a7|a6|a5|a4|a3|a2|a1|a0|d7|d6|d5|d4|d3|d2|d1|d0| * +--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+ ****************************************************************************** Movem_mask movem.l d1-d3,-(sp) clr.l d3 eventual register map movem_loop bsr Save_place bsr Encode_reg get d0-d7/a0-a7 cmp.b #16,d0 PC/CCR/SR/USP/other? bcc mask_done move.b d0,d1 save start jsr GetNonSpace look for / or - cmp.b #'/',d0 beq just_onereg cmp.b #'-',d0 bne last_one bsr Encode_reg get termination cmp.b #16,d0 PC/CCR/SR/USP? bcc mask_err move.b d0,d2 temp eor.b d1,d2 btst #3,d2 see if ax-dy or dx-ay form given bne mask_err cmp.b d0,d1 in Rx-Ry, make sure y > x bcc mask_err mask_set bchg d1,d3 set this bit bne mask_err reg declared twice if it was already set addq.b #1,d1 cmp.b d1,d0 bcc mask_set bsr Save_place jsr GetNonSpace cmp.b #'/',d0 group separator beq movem_loop jsr back_up put back non-'/' character bra mask_done just_onereg bchg d1,d3 see if this reg has been specified yet bne mask_err reg declared twice bra movem_loop last_one tst.w d3 have we gone through the loop yet? beq.s no_list jsr back_up put back non '-' character bchg d1,d3 see if this reg was used before bne mask_err reg declared twice mask_done tst.w d3 have we gone through the loop yet? beq.s no_list move.l d3,d0 d0 has mask on exit moveq #16-1,d1 see if only one bit is set moveq #1,d2 check_loop ror.w #1,d2 start with a7 only, then a6, then ... cmp.w d2,d0 ... a1, a0, d7, d6 ... d1, d0 dbeq d1,check_loop bne.s movem_exit no_list bsr Restore_ln go back to where we were clr.w d0 indicate no mask movem_exit movem.l (sp)+,d1-d3 rts ****************************************************************************** * This subroutine reverses the bit order of a 16 bit value in d0.w * That is, bit 15 <--> bit 0, bit 14 <--> bit 1, etc. ****************************************************************************** Reverse16 movem.w d1-d2,-(sp) move.w #15,d2 # of bits-1 to reverse reverse_lup roxl.w #1,d0 shift out ms bit of mask roxr.w #1,d1 shift toward ls bit of new mask dbf d2,reverse_lup move.w d1,d0 movem.w (sp)+,d1-d2 rts page azm_EA ****************************************************************************** * * This routine will assemble the upcoming characters in the line buffer. * It will leave a value indicating the type of operand in EA_type. * Any necessary extension word (including immediate) will be in EA_ext, 32 bits * * On exit the next char in the buffer will be the first character not * part of the effective address specifier. * ****************************************************************************** azm_EA movem.l d0-d7/a0-a6,-(sp) clr.l EA_ext bsr Save_place remember position in line buffer jsr GetNonSpace get first char of EA jsr upper_case cmp.b #'#',d0 immediate mode? beq azmEA_imm cmp.b #'(',d0 indirect mode? beq azmEA_indr cmp.b #'-',d0 predecrement or offset? beq azmEA_neg cmp.b #'A',d0 if it doesn't start 'A'-'Z' bcs azmEA_indx ... then it isn't a symbol but cmp.b #'Z',d0 ... it could be an offset expression bhi azmEA_indx * It starts with a letter. It could be a register or a symbol. bsr Restore_ln go back to start of symbol bsr Movem_mask tst.w d0 beq.s not_reglist move.l d0,EA_ext move.w #REG_LIST,EA_type bra azmEA_exit not_reglist bsr Encode_reg see if Dx, Ax, PC, SSR, CCR, or USP cmp.b #20,d0 not a register? beq.s azmEA_sym cmp.b #16,d0 PC? beq unknownEA no mode starts with "PC..." cmp.b #17,d0 beq azmEA_SR cmp.b #18,d0 beq azmEA_CCR cmp.b #19,d0 beq azmEA_USP move.b d0,EA_field mode will be 001 for Ax and 000 for Dx cmp.b #8,d0 bcs.s azmEA_Dx move.w #ADDR_REG,EA_type bra azmEA_exit azmEA_Dx move.w #DATA_REG,EA_type bra azmEA_exit azmEA_SR move.w #SR_REG,EA_type move.b #$3C,EA_field mode of 111, reg of 100 bra azmEA_exit azmEA_CCR move.w #CCR_REG,EA_type move.b #$3C,EA_field mode of 111, reg of 100 bra azmEA_exit azmEA_USP move.w #USP_REG,EA_type bra azmEA_exit azmEA_sym bsr Restore_ln go back to start of symbol bra azmEA_indx1 * We have seen a '-'. It could be the start of a predecrement mode or * the offset of a displacement mode. azmEA_neg jsr GetNonSpace cmp.b #'(',d0 beq azmEA_dec bsr Restore_ln must back up to the '-' in input bra azmEA_indx1 azmEA_dec bsr Encode_reg cmp.b #16,d0 PC, SR, CCR, or USP? bcc unknownEA sub.b #8,d0 bcs unknownEA D0-D7? move.w #PREDEC,EA_type or.b #$20,d0 mode is 100, reg is in d0 move.b d0,EA_field jsr GetNonSpace cmp.b #')',d0 must have a ')' here bne unknownEA bra azmEA_exit * It must be of the form , (PC), (PC,Rx) * (Ax), or (Ax,Ry) azmEA_indx jsr Back_up azmEA_indx1 jsr GetValue get absolute value or an offset move.l d0,EA_ext save offset value jsr GetNonSpace cmp.b #'(',d0 see if absolute bne azmEA_abs azmEA_indr bsr Check_reg cmp.b #8,d0 make sure a0-a7/PC bcs unknownEA cmp.b #17,d0 check for SR, CCR, or USP bcc unknownEA move.b d0,d7 remember base register * We have seen "(PC" or "(Ax". * See if a comma or a ) follows. jsr GetNonSpace cmp.b #',',d0 see if some indexed mode bne azm_noindx bsr Check_reg cmp.b #16,d0 is it PC/SR/CCR/USP? bcc unknownEA move.w d0,d6 save index register * Indexed indirect modes allow only an 8-bit offset. See if it is. move.l EA_ext,d0 move.b d0,d1 ext.w d1 ext.l d1 cmp.l d1,d0 bne offseterr * Now we've seen "(PC,Rx" or "(Ax,Ry". * See if there is a length specification. jsr GetNonSpace cmp.b #'.',d0 beq.s OffIndxsize moveq #word_len,d5 default of word bra.s OffIndxcont OffIndxsize jsr GetByte get length qualifier bsr Encode_len cmp.b #byte_len,d0 .B is not allowed here beq unknownEA cmp.b #short_len,d0 .S extension makes no sense here beq unknownEA move.w d0,d5 save index size jsr GetNonSpace OffIndxcont cmp.b #')',d0 bne unknownEA must have ')' at this point ror.w #6,d5 put a 1 in bit 11 if long word and.l #$0800,d5 make sure only bit 11 can be set ror.w #4,d6 put register number up in ms 4 bits or.w d6,d5 now have index reg and index size move.b EA_ext+3,d5 stick in offset move.l d5,EA_ext save extension word * We've made the extension word. * Now save the EA field and EA type words cmp.b #16,d7 beq.s formpcindx move.w #INDRINDXDIS,EA_type eor.b #$38,d7 l.s. 8 bits are 00110xxx, as in Ax move.b d7,EA_field (remember that encoding is A0 -> 8, etc) bra azmEA_exit formpcindx move.w #PCINDXDIS,EA_type move.b #$3B,EA_field PC indirect with index and displacement bra azmEA_exit * At this point we've seen "(PC" or "(Ax". * We also know the next character isn't a comma. We must have a * non-indexed mode on our hands. * Indirect w/displacement modes allow only a 16-bit offset. See if it is. azm_noindx cmp.b #')',d0 a ')' must appear here bne unknownEA move.l EA_ext,d0 see if 16-bit offset fits move.w d0,d1 ext.l d1 cmp.l d1,d0 bne offseterr cmp.b #16,d7 see if PC relative or Ax relative beq.s formpcdisp tst.l d0 see if there is no offset beq.s azm_nooff move.w #INDRDISP,EA_type or.b #$28,d7 mode is 101, reg is in d7 already move.b d7,EA_field bra azmEA_exit formpcdisp move.w #PCDISP,EA_type move.b #$3A,EA_field mode is 111, reg is 010 bra azmEA_exit * Right now we've seen "(An)". Check if it is "(An)+". azm_nooff jsr GetNonSpace cmp.b #'+',d0 beq.s azmEA_post jsr Back_up put back non-"+" character move.w #INDIRECT,EA_type eor.b #$18,d7 mode is 010, reg is in d7 already move.b d7,EA_field (remember that A0 -> 8) bra azmEA_exit azmEA_post move.w #POSTINC,EA_type or.b #$18,d7 mode is 011, reg is in d7 already move.b d7,EA_field bra azmEA_exit * Right now we know it is an absolute long or short. Find out which. azmEA_abs jsr Back_up put back non-'(' character move.l EA_ext,d0 get offset bpl.s azmEA_abs1 neg.l d0 azmEA_abs1 cmp.l #$8000,d0 bcs.s azmEA_abs2 move.w #ABSLONG,EA_type absolute long address move.b #$39,EA_field bra azmEA_exit azmEA_abs2 move.w #ABSSHORT,EA_type absolute short address move.b #$38,EA_field bra azmEA_exit * We have seen a '#', so it must be immediate data azmEA_imm jsr GetValue move.l d0,EA_ext save immediate data move.b #$3C,EA_field 6 bit EA encoding move.w #IMMEDIATE,EA_type bra azmEA_exit azmEA_exit movem.l (sp)+,d0-d7/a0-a6 rts page assembly routines Azm_xBCD cmp.b #No_len,operand_len bne IB_lenerr implicit byte length cmp.w #DATA_REG,src_type bne.s Azm_xBCD2 cmp.w #DATA_REG,dst_type bne Illegal_dst move.w d7,d0 basic xBCD Dy,Dx opcode bsr Dest_9to11 insert dest field bsr Src_0to2 insert source field bsr opcode_d0 store opcode rts Azm_xBCD2 cmp.w #PREDEC,src_type bne Illegal_src cmp.w #PREDEC,dst_type bne Illegal_dst move.w d7,d0 basic ABCD -(Ay),-(Ax) opcode bset #3,d0 indicate predecrement mode bsr Dest_9to11 insert dest field bsr Src_0to2 insert source field bsr opcode_d0 store opcode rts * This following ADD/SUB routines have the most complex opcode encoding. * Since one 32-bit value must provide opcode bits for op/opA/opI/opQ * instructions, the following encoding is used: * D7[15:12] = ADD/SUB/ADDA/SUBA upper nibble * D7[11:8] = ADDI/SUBI [11:8] nibble * D7[7:0] = ADDQ/SUBQ upper opcode byte Azm_ADSB cmp.w #ADDR_REG,dst_type beq.s Azm_ASA cmp.w #IMMEDIATE,src_type beq Azm_ASI move.w #$FFF0,d0 and.w src_type,d0 beq Illegal_src catch SR,CCR,USP sources and.w #$f000,d7 leave only proper bits cmp.w #DATA_REG,dst_type bne.s Azm_ADSB2 bsr Src_A_byte check for proper use of An move.w d7,d0 basic ADD/SUB ,Dn opcode bsr SizeBits_67 insert size field bsr Dest_9to11 insert destination field bsr Stndrd_sea merge ea, emit opcode and extension words rts Azm_ADSB2 move.w #$3480,d0 see if destination is allowed and.w dst_type,d0 beq Illegal_dst move.w d7,d0 basic ADD Dn, opcode bset #8,d0 indicate is the destination bsr SizeBits_67 insert length field bsr Src_9to11 insert source Dn field bsr stndrd_dea merge ea, emit opcode and extension word rts Azm_ASA cmp.w #ADDR_REG,dst_type bne Illegal_dst and.w #$F000,d7 leave only proper bits move.w d7,d0 basic ADDA/SUBA opcode bsr SizeBit_WL8 insert length field bsr stndrd_sea merge ea, emit opcode and extension word rts Azm_ASI cmp.w #IMMEDIATE,src_type bne Illegal_src move.w #$BF80,d0 and.w dst_type,d0 see if dest is allowable beq Illegal_dst cmp.w #DATA_REG,dst_type see if we can optimize bne.s Azm_ASI2 cmp.l #8,src_ext bgt.s Azm_ASI2 if 1 <= # <= 8 then use ASQ cmp.l #1,src_ext bge.s Azm_ASQ Azm_ASI2 and.w #$0F00,d7 leave only proper bits move.w d7,d0 basic ADDI/SUBI opcode bsr SizeBits_67 insert length field bsr dstEA_field merge ea field and emit opcode bsr stndrd_imm emit immediate data bsr stndrd_dext emit any ea extension words rts Azm_ASQ cmp.w #IMMEDIATE,src_type bne Illegal_src move.w #$FF80,d0 see if destination is legal and.w dst_type,d0 beq Illegal_dst cmp.w #ADDR_REG,dst_type An can be only .W or .L bne Azm_ASQ1 bsr WL_only Azm_ASQ1 cmp.l #8,src_ext see if number is in range bgt Range_error cmp.l #1,src_ext blt Range_error lsl.w #8,d7 position opQ opcode bits move.w d7,d0 basic ADDQ/SUBQ opcode bsr SizeBits_67 insert length field bsr QData merge in quick data field bsr stndrd_dea merge ea, emit opcode and ext. word(s) rts Azm_opX cmp.w #DATA_REG,src_type bne.s Azm_opX2 cmp.w #DATA_REG,dst_type bne Illegal_dst move.w d7,d0 basic opX Dy,Dx opcode bsr SizeBits_67 insert length field bsr Dest_9to11 insert destination field bsr Src_0to2 insert source field bsr opcode_d0 assemble in opcode rts Azm_opX2 cmp.w #PREDEC,src_type bne Illegal_src cmp.w #PREDEC,dst_type bne Illegal_dst move.w d7,d0 basic opX (Ay)-,(Ax)- opcode bset #3,d0 indicate predecrement mode bsr SizeBits_67 insert length field bsr Dest_9to11 insert destination field bsr Src_0to2 insert source field bsr opcode_d0 rts Azm_ANDOR cmp.w #IMMEDIATE,src_type beq Azm_ANDORI clr.b d7 forget lower bits (for immediate info) cmp.w #DATA_REG,dst_type bne Azm_ANDOR2 move.w #$BFF0,d0 see if src is allowable and.w src_type,d0 beq Illegal_src move.w d7,d0 basic AND ,Dn opcode bsr SizeBits_67 insert length field bsr Dest_9to11 insert dest reg field bsr stndrd_sea merge ea, emit opcode and ext. word(s) rts Azm_ANDOR2 cmp.w #DATA_REG,src_type bne Illegal_src move.w #$3F80,d0 see if dest is allowable and.w dst_type,d0 beq Illegal_dst move.w d7,d0 basic AND Dn, opcode bset #8,d0 indicate is destination bsr SizeBits_67 insert length field bsr Src_9to11 insert source reg field bsr stndrd_dea merge ea, emit opcode and ext. word(s) rts Azm_ANDORI cmp.w #IMMEDIATE,src_type bne Illegal_src lsl.w #8,d7 position immediate opcode bits cmp.w #SR_REG,dst_type beq.s Azm_AOSR cmp.w #CCR_REG,dst_type beq.s Azm_AOCCR move.w #$BF80,d0 see if dest is allowable and.w dst_type,d0 beq Illegal_dst move.w d7,d0 basic ANDI opcode bsr SizeBits_67 insert length field bsr dstEA_field merge ea field and emit opcode bsr stndrd_imm emit immediate word(s) bsr stndrd_dext emit any ea extension words rts Azm_AOSR cmp.b #no_len,operand_len bne IW_lenerr implicit WORD length move.w d7,d0 get upper 8 opcode bits move.b #$7C,d0 turn opcode into ,SR opcode bsr opcode_d0 assemble it in move.l src_ext,d0 get immediate value bsr opcode_d0 assemble in value rts Azm_AOCCR cmp.b #no_len,operand_len bne IB_lenerr implicit BYTE length move.l src_ext,d1 get immediate value clr.b d1 bne Range_error larger than byte move.w d7,d0 get upper 8 opcode bits move.b #$3C,d0 turn opcode into ,CCR opcode bsr opcode_d0 assemble it in move.l src_ext,d0 get immediate value bsr opcode_d0 assemble in value rts Azm_shift cmp.w #No_EA,dst_type beq.s Azm_shftmem cmp.w #IMMEDIATE,src_type beq.s Azm_shftimm cmp.w #DATA_REG,src_type bne Illegal_src cmp.w #DATA_REG,dst_type bne Illegal_dst move.w d7,d0 basic Dy,Dx opcode bset #5,d0 indicate Dy has count bsr SizeBits_67 bsr Src_9to11 bsr Dst_0to2 bsr opcode_d0 emit opcode rts Azm_shftimm move.w d7,d0 basic #n,Dx opcode bsr SizeBits_67 bsr count_9to11 bsr Dst_0to2 bsr opcode_d0 emit opcode rts Azm_shftmem move.w #$3F80,d0 see if ea is allowable and.w src_type,d0 beq Illegal_src cmp.b #No_len,operand_len bne IB_lenerr implicit byte length move.w d7,d0 basic opcode bsr stndrd_sea merge ea, emit opcode and ext. word(s) rts Azm_Bxx cmp.w #No_EA,dst_type bne Illegal_dst move.w #$0180,d0 see if ABS LONG or ABS SHORT and.w src_type,d0 beq Illegal_src move.w d7,d0 basic branch opcode move.l src_ext,d1 get address subq.l #2,d1 current is PC+2 sub.l azm_address,d1 calculate offset move.b d1,d2 see if offset fits in 8 bits ext.w d2 ext.l d2 cmp.l d2,d1 beq.s Azm_Bxxb move.w d1,d2 see if offset fits in 16 bits ext.l d2 cmp.l d2,d1 bne offseterr bsr opcode_d0 emit opcode with 00 displacement move.w d1,d0 bsr opcode_d0 save 16-bit displacement rts Azm_Bxxb move.b d1,d0 merge in 8-bit offset bsr opcode_d0 assemble it in rts Azm_Bitop cmp.b #no_len,operand_len bne Unsized_err move.w #$BF80,d0 see if dest is allowable and.w dst_type,d0 beq Illegal_dst cmp.w #DATA_REG,src_type bne Azm_Bitop2 move.w #$0100,d0 basic Bitop Dn, opcode or.w d7,d0 turn generic Bitop into specific opcode bsr Src_9to11 insert count reg field bsr stndrd_dea merge ea field, emit opcode & ext. words rts Azm_Bitop2 cmp.w #IMMEDIATE,dst_type bne Illegal_dst move.w #$0800,d0 basic Bitop #n, opcode or.w d7,d0 turn generic Bitop into specific opcode bsr dstEA_field merge ea field, emit opcode move.l #src_ext,d0 get shift count and.l #$FF,d0 leave only lower byte bsr opcode_d0 emit shift constant bsr stndrd_dext emit extension word(s) rts Azm_BSR cmp.w #No_EA,dst_type bne Illegal_dst move.w #$0180,d0 see if ABS LONG or ABS SHORT and.w src_type,d0 beq Illegal_src move.w d7,d0 basic BSR opcode move.l src_ext,d1 get address subq.l #2,d1 current is PC+2 sub.l azm_address,d1 calculate offset move.b d1,d2 see if offset fits in 8 bits ext.w d2 ext.l d2 cmp.l d2,d1 beq.s Azm_BSRb move.w d1,d2 see if offset fits in 16 bits ext.l d2 cmp.l d2,d1 bne offseterr bsr opcode_d0 emit opcode with 00 displacement move.w d1,d0 bsr opcode_d0 save 16-bit displacement rts Azm_BSRb move.b d1,d0 merge in 8-bit offset bsr opcode_d0 assemble it in rts Azm_CHK cmp.b #no_len,operand_len bne IW_lenerr implicit word length cmp.w #DATA_REG,dst_type bne Illegal_dst move.w #$BFF0,d0 see if source is allowable and.w src_type,d0 beq Illegal_src move.w d7,d0 basic CHK opcode bsr Dest_9to11 insert Dn field bsr stndrd_sea merge ea, emit opcode and ext. word(s) rts Azm_monop cmp.w #No_EA,dst_type make sure there isn't a second operand bne Illegal_dst and.w #$BF80,src_type see if an allowable mode has been chosen beq Illegal_src move.w d7,d0 basic CLR opcode bsr SizeBits_67 make length field bsr stndrd_sea put opcode in memory rts Azm_CMP cmp.w #IMMEDIATE,src_type beq Azm_CMPI cmp.w #ADDR_REG,dst_type beq Azm_CMPA cmp.w #POSTINC,dst_type beq Azm_CMPM cmp.w #DATA_REG,dst_type bne Illegal_dst move.w #$B000,d0 basic CMP opcode bsr SizeBits_67 make length field bsr Dest_9to11 insert dest field bsr stndrd_sea put opcode in memory rts Azm_CMPA cmp.w #ADDR_REG,dst_type bne Illegal_dst move.w #$B0C0,d0 basic CMPA opcode bsr SizeBit_WL8 bsr Dest_9to11 insert dest field bsr stndrd_sea rts Azm_CMPI move.w #$BF80,d0 see if dest field is allowable and.w dst_type,d0 beq Illegal_dst move.w #$0C00,d0 basic CMPI opcode bsr SizeBits_67 insert size field bsr dstEA_field store opcode bsr stndrd_imm save immediate words bsr stndrd_dext form destination extension words rts Azm_CMPM cmp.w #POSTINC,dst_type bne Illegal_dst only (Ax)+, (Ay)+ is allowed cmp.w #POSTINC,src_type bne Illegal_src only (Ax)+, (Ay)+ is allowed move.w #$B108,d0 basic CMPM opcode bsr SizeBits_67 insert size field bsr Dest_9to11 put dest reg in [9:11] bsr Src_0to2 put source reg in [2:0] bsr Opcode_d0 save it rts Azm_DBxx cmp.b #no_len,operand_len bne IW_lenerr implicit word length cmp.w #DATA_REG,src_type bne Illegal_src move.w #$0180,d0 see if ABS LONG or ABS SHORT and.w dst_type,d0 beq Illegal_dst move.l dst_ext,d1 get address subq.l #2,d1 current is PC+2 sub.l azm_address,d1 calculate offset move.w d1,d2 see if offset fits in 16 bits ext.l d2 cmp.l d2,d1 bne offseterr move.w d7,d0 get basic opcode bsr Src_0to2 merge in count register field bsr opcode_d0 emit opcode move.w d1,d0 bsr opcode_d0 emit diplacement word rts Azm_MULDIV cmp.w #DATA_REG,dst_type dest must be Dn bne Illegal_dst move.w src_type,d0 make sure src is allowable and.w #$BFF0,d0 beq Illegal_src cmp.b #no_len,operand_len bne IW_lenerr implicit word length move.w d7,d0 basic opcode bsr Dest_9to11 insert destination field bsr Stndrd_sea emit opcode and extension words rts Azm_EOR cmp.w #IMMEDIATE,src_type beq.s Azm_EORI cmp.w #DATA_REG,src_type bne Illegal_src move.w dst_type,d0 see if dest is allowable and.w #$BF80,d0 beq Illegal_dst move.w d7,d0 basic EOR opcode bsr SizeBits_67 insert size field bsr Src_9to11 insert source field bsr Stndrd_dea add ea field, emit opcode and extension words rts Azm_EORI cmp.w #SR_REG,dst_type beq.s Azm_EORSR cmp.w #CCR_REG,dst_type beq.s Azm_EORCCR cmp.w #IMMEDIATE,src_type bne Illegal_src move.w dst_type,d0 see if dest is allowable and.w #$BF80,d0 beq Illegal_dst move.w #$0A00,d0 basic EORI opcode bsr SizeBits_67 insert size field bsr dstEA_field store opcode bsr stndrd_imm output immediate extension words bsr stndrd_dext rts Azm_EORSR cmp.b #no_len,operand_len bne IW_lenerr implicit WORD length move.w #$0A7C,d0 EOR ,SR opcode bsr opcode_d0 assemble it in move.l src_ext,d0 get immediate value bsr opcode_d0 assemble in value rts Azm_EORCCR cmp.b #no_len,operand_len bne IB_lenerr implicit BYTE length move.l src_ext,d1 get immediate value clr.b d1 bne Range_error larger than byte move.w #$0A3C,d0 EOR ,CCR opcode bsr opcode_d0 assemble it in move.l src_ext,d0 get immediate value bsr opcode_d0 assemble in value rts Azm_EXG cmp.b #no_len,operand_len bne IL_lenerr implicit LONG length cmp.w #DATA_REG,src_type bne.s Azm_EXG2 cmp.w #DATA_REG,dst_type bne.s Azm_EXG1 move.w d7,d0 basic EXG Dx,Dy opcode bra.s Azm_EXGfill Azm_EXG1 cmp.w #ADDR_REG,dst_type bne Illegal_dst cmp.w #DATA_REG,src_type bne Illegal_src move.w #$C188,d0 basic EXG Dx,Ay opcode bra.s Azm_EXGfill Azm_EXG2 cmp.w #ADDR_REG,src_type bne Illegal_src cmp.w #ADDR_REG,dst_type bne Azm_EXG3 move.w #$C148,d0 basic EXG Ax,Ay opcode Azm_EXGfill bsr Src_9to11 merge in first register bsr Dst_0to2 merge in second register bra.s Azm_EXG_xit Azm_EXG3 cmp.w #DATA_REG,dst_type bne Illegal_dst move.w #$C188,d0 basic EXG Ax,Dy opcode bsr Src_0to2 Ax must be here in mixed EXGs bsr Dest_9to11 Dx must be here in mixed EXGs Azm_EXG_xit bsr opcode_d0 emit opcode rts Azm_EXT cmp.w #No_EA,dst_type bne Illegal_dst cmp.w #DATA_REG,src_type bne Illegal_src bsr WL_only make sure size is ok move.w d7,d0 basic EXT opcode, word length cmp.b #long_len,operand_len bne.s Azm_EXT1 bset #6,d0 indicate long length Azm_EXT1 bsr Src_0to2 merge in affected register field bsr opcode_d0 assemble in opcode rts Azm_JMP cmp.w #No_EA,dst_type bne Illegal_dst move.w #$27E0,d0 see if is legit and.w src_type,d0 beq Illegal_src move.w d7,d0 basic JMP opcode bsr stndrd_sea merge , emit opcode and extensions rts Azm_JSR cmp.w #No_EA,dst_type bne Illegal_dst move.w #$27E0,d0 see if is legit and.w src_type,d0 beq Illegal_src move.w d7,d0 basic JSR opcode bsr stndrd_sea merge , emit opcode and extensions rts Azm_STOP cmp.w #No_EA,dst_type bne Illegal_dst cmp.w #IMMEDIATE,src_type bne Illegal_src cmp.b #no_len,operand_len bne Unsized_err move.l src_ext,d0 get immediate value swap d0 tst.w d0 see if it's a 16 bit value bne Range_error move.w d7,d0 get STOP opcode bsr opcode_d0 emit opcode swap d0 recall 16 bit value bsr opcode_d0 emit SR value rts Azm_noop cmp.w #No_EA,src_type bne Illegal_src cmp.w #No_EA,dst_type bne Illegal_dst cmp.b #no_len,operand_len bne unsized_err unsized instruction move.w d7,d0 bsr opcode_d0 emit opcode rts Azm_LEA cmp.w #ADDR_REG,dst_type bne Illegal_dst move.w #$27E0,d0 see if source is allowed and.w src_type,d0 beq Illegal_src move.w d7,d0 basic LEA opcode bsr Dest_9to11 insert dest reg field bsr stndrd_sea merge ea, emit opcode and ext. word(s) rts Azm_LINK cmp.w #ADDR_REG,src_type bne Illegal_src cmp.w #IMMEDIATE,dst_type bne Illegal_dst move.l dst_ext,d0 move.w d0,d1 see if displacement will fit in 16 bits ext.l d1 cmp.l d0,d1 bne Offseterr displacement too large move.w d7,d0 basic LINK opcode bsr Src_0to2 insert link register field bsr opcode_d0 emit opcode move.w d1,d0 bsr opcode_d0 emit displacement rts Azm_MOVE cmp.w #SR_REG,src_type pick out any unusual types beq Azm_fromSR cmp.w #CCR_REG,src_type beq Azm_fromCCR cmp.w #USP_REG,src_type beq Azm_fromUSP cmp.w #SR_REG,dst_type beq Azm_toSR cmp.w #CCR_REG,dst_type beq Azm_toCCR cmp.w #USP_REG,dst_type beq Azm_toUSP cmp.w #ADDR_REG,dst_type beq Azm_MOVEA move.w #$BF80,d0 see if dest is allowable and.w dst_type,d0 beq Illegal_dst cmp.w #IMMEDIATE,src_type see if MOVEQ can be used bne.s Azm_notMQ cmp.w #DATA_REG,dst_type bne.s Azm_notMQ cmp.b #long_len,operand_len bne.s Azm_notMQ move.l src_ext,d0 cmp.l #-128,d0 blt.s Azm_notMQ cmp.l #127,d0 bgt Azm_notMQ move.b #no_len,operand_len MOVEQ is implicitly LONG bra Azm_MOVEQ Azm_notMQ clr.w d0 first create the length field clr.w d1 move.b operand_len,d1 lea Fab_table,a1 move.b 0(a1,d1.w),d0 get stupid length field beq Bad_size .s can't be used (signified by 00) move.b dst_field,d1 make destination field move.b d1,d2 and.w #$0007,d1 extract register field and.w #$0038,d2 extract mode field lsl.w #3,d1 swap positions of mode and reg lsr.w #3,d2 or.w d1,d0 stick in reg field or.w d2,d0 stick in mode field lsl.w #6,d0 move to proper location bsr stndrd_sea merge s, emit opcode, src ext. words bsr stndrd_dext emit dest extension words rts Azm_fromUSP cmp.w #ADDR_REG,dst_type bne Illegal_dst cmp.b #no_len,operand_len bne IL_lenerr implicit LONG length move.w #$4E68,d0 basic MOVE USP,An opcode bsr Dst_0to2 merge in destination field bsr opcode_d0 emit opcode rts Azm_toUSP cmp.w #ADDR_REG,src_type bne Illegal_src cmp.b #no_len,operand_len bne IL_lenerr implicit LONG length move.w #$4E60,d0 basic MOVE An,USP opcode bsr Src_0to2 merge in source field bsr opcode_d0 emit opcode rts Azm_fromCCR move.w #$BF80,d0 see if dest is allowed and.w dst_type,d0 beq Illegal_dst bsr W_only make sure it's a word length move.w #$42C0,d0 basic MOVE CCR, bsr stndrd_dea merge , emit opcode and ext. word(s) rts Azm_fromSR move.w #$BF80,d0 see if dest is allowed and.w dst_type,d0 beq Illegal_dst bsr W_only make sure it's a word length move.w #$40C0,d0 basic MOVE SR, bsr stndrd_dea merge , emit opcode and ext. word(s) rts Azm_toCCR move.w #$BFF0,d0 see if source is allowable and.w src_type,d0 beq Illegal_src bsr W_only make sure word length move.w #$44C0,d0 basic MOVE ,CCR operation bsr stndrd_sea merge , emit opcode and ext. word(s) rts Azm_toSR move.w #$BFF0,d0 see if source is allowable and.w src_type,d0 beq Illegal_src bsr W_only make sure word length move.w #$46C0,d0 basic MOVE ,SR operation bsr stndrd_sea merge , emit opcode and ext. word(s) rts Azm_MOVEA cmp.w #ADDR_REG,dst_type bne Illegal_dst move.w #$FFF0,d0 see if src is allowable and.w src_type,d0 beq Illegal_src move.b operand_len,d0 bsr WL_only make sure size is OK and.w #$0002,d0 leave only bit 1 bchg #1,d0 =0 if long, 1 otherwise ror.w #5,d0 put bit in bit #12 or.w #$2040,d0 make basic MOVEA opcode bsr Dest_9to11 insert destination field bsr stndrd_sea merge , emit opcode and ext. word(s) rts Azm_MOVEM bsr WL_only only word and long are allowed cmp.b #long_len,operand_len bne.s Azm_MM1 bset #6,d7 make opcode LONG Azm_MM1 cmp.w #REG_LIST,src_type bne.s Azm_MOVEM2 move.w dst_type,d0 and.w #$2F80,d0 see if destination is allowed beq Illegal_dst move.w d7,d0 basic opcode bsr dstEA_field merge and emit opcode move.l src_ext,d0 get register list cmp.w #PREDEC,dst_type we must reverse list if predecrement bne.s Azm_MM2 bsr Reverse16 flip those bits Azm_MM2 bsr opcode_d0 emit register list mask bsr stndrd_dext emit any dest. extension word(s) rts Azm_MOVEM2 cmp.w #REG_LIST,dst_type bne Illegal_dst move.w src_type,d0 and.w #$37E0,d0 see if source is allowable beq Illegal_src move.w d7,d0 get basic opcode bset #10,d0 indicate direction of move bsr srcEA_field merge and emit opcode move.l dst_ext,d0 get register list mask bsr opcode_d0 emit register list mask bsr stndrd_sext emit any source extension word(s) rts Azm_MOVEP bsr WL_only make sure size is OK cmp.w #DATA_REG,src_type bne Azm_MOVEP2 cmp.w #INDRDISP,dst_type bne Illegal_dst clr.w d0 bsr SizeBits_67 lsr.w #1,d0 bclr #5,d0 in case it is set (if it was word_len) or.w #$0188,d0 turn into MOVEP Dx,d(Ay) opcode bsr Dst_0to2 insert addr reg field bsr Src_9to11 insert data reg field bsr opcode_d0 emit opcode move.l dst_ext,d0 get displacement bsr opcode_d0 emit displacement rts Azm_MOVEP2 cmp.w #INDRDISP,src_type bne Illegal_src cmp.w #DATA_REG,dst_type bne Illegal_dst clr.w d0 bsr SizeBits_67 lsr.w #1,d0 bclr #5,d0 in case it is set (if it was word_len) or.w #$0108,d0 turn into MOVEP d(Ay),Dx opcode bsr Src_0to2 insert addr reg field bsr Dest_9to11 insert data reg field bsr opcode_d0 emit opcode move.l src_ext,d0 get displacement bsr opcode_d0 emit displacement rts Azm_MOVEQ cmp.w #IMMEDIATE,src_type bne Illegal_src cmp.w #DATA_REG,dst_type bne Illegal_dst cmp.b #no_len,operand_len bne IL_lenerr implicit LONG length move.l src_ext,d1 get immediate value cmp.l #127,d1 bgt Range_error too large cmp.l #-128,d1 blt Range_error too small move.w #$7000,d0 basic MOVEQ opcode bsr Dest_9to11 insert dest reg field move.b d1,d0 insert data field bsr opcode_d0 emit opcode rts Azm_NBCD cmp.w #No_EA,dst_type bne Illegal_dst move.w #$BF80,d0 see if operand is allowable and.w src_type,d0 beq Illegal_src cmp.b #no_len,operand_len bne IB_lenerr implicit byte length move.w d7,d0 basic NBCD opcode bsr stndrd_sea merge , emit opcode and ext. word(s) rts Azm_negs cmp.w #No_EA,dst_type bne Illegal_dst move.w #$BF80,d0 see if operand is allowable and.w src_type,d0 beq Illegal_src move.w d7,d0 get basic opcode bsr SizeBits_67 insert length field bsr stndrd_sea merge , emit opcode and ext. word(s) rts Azm_PEA cmp.w #No_EA,dst_type bne Illegal_dst move.w #$27E0,d0 see if operand is allowable and.w src_type,d0 beq Illegal_src cmp.b #no_len,operand_len bne IL_lenerr implicit LONG length move.w d7,d0 basic PEA opcode bsr stndrd_sea merge , emit opcode & ext. word(s) rts Azm_Sxx cmp.b #no_len,operand_len bne IB_lenerr implicit byte length cmp.w #No_EA,dst_type bne Illegal_dst move.w #$BF80,d0 see if operand is allowable and src_type,d0 beq Illegal_src move.w d7,d0 get basic opcode bsr stndrd_sea merge , emit opcode & ext. word(s) rts Azm_SWAP cmp.w #No_EA,dst_type bne Illegal_dst cmp.w #DATA_REG,src_type bne Illegal_src cmp.b #no_len,operand_len bne IW_lenerr implicit word length move.w d7,d0 basic SWAP instruction bsr Src_0to2 insert reg field bsr opcode_d0 emit opcode rts Azm_TAS cmp.w #No_EA,dst_type bne Illegal_dst move.w #$BF80,d0 see if operand is kosher and.w src_type,d0 beq Illegal_src cmp.b #no_len,operand_len bne IW_lenerr implicit word length move.w d7,d0 basic TAS opcode bsr stndrd_sea merge , emit opcode and ext. word(s) rts Azm_TRAP and.w #No_EA,dst_type bne Illegal_dst cmp.w #IMMEDIATE,src_type bne Illegal_src cmp.b #no_len,operand_len bne unsized_err unsized instruction move.l src_ext,d1 get immediate value move.w d1,d0 and.l #$FFFFFFF0,d1 bne Range_error vector < 0 or vector > 15 or.w d7,d0 merge generic opcode with vector # bsr opcode_d0 emit opcode rts Azm_UNLK cmp.w #No_EA,dst_type bne Illegal_dst cmp.w #ADDR_REG,src_type bne Illegal_src move.w d7,d0 basic UNLK opcode bsr Src_0to2 merge in link register field bsr opcode_d0 emit opcode rts page error messages lenerrmess dc.b 'Bad length qualifier',0 WO_mess dc.b 'WORD length only',0 WL_mess dc.b 'WORD/LONG length only',0 IB_mess dc.b 'Implicit byte length',0 IW_mess dc.b 'Implicit word length',0 IL_mess dc.b 'Implicit long length',0 BS_mess dc.b 'That operation size doesn''t make sense',0 unsiz_mess dc.b 'Unsized instruction',0 rng_mess dc.b 'Immediate value not in range',0 regerrmess dc.b 'Unrecognized register name',0 unknownmess dc.b 'Invalid operand',0 offsetmess dc.b 'Offset too large',0 Ill_srcmess dc.b 'Illegal source operand',0 Ill_dstmess dc.b 'Illegal destination operand',0 op_error dc.b 'Bad opcode',0 un_mess dc.b 'Unknown operand',0 odd_mess dc.b 'Can''t assemble to odd address',0 conf_mess dc.b 'Label with different value already exists',0 mask_errmes dc.b 'Register list specified incorrectly',0 Illegal_src lea Ill_srcmess,a1 jmp CommonErr Illegal_dst lea Ill_dstmess,a1 jmp CommonErr bad_opcode lea op_error,a1 opcode too long if we fell through jmp CommonErr unknownEA lea unknownmess,a1 jmp CommonErr offseterr lea offsetmess,a1 jmp CommonErr Bad_size lea BS_mess,a1 jmp CommonErr WO_lenerr lea WO_mess,a1 jmp CommonErr WL_lenerr lea WL_mess,a1 jmp CommonErr Unsized_err lea unsiz_mess,a1 jmp CommonErr Range_error lea rng_mess,a1 jmp CommonErr regerr lea regerrmess,a1 jmp CommonErr IB_lenerr lea IB_mess,a1 jmp CommonErr IW_lenerr lea IW_mess,a1 jmp CommonErr IL_lenerr lea IL_mess,a1 jmp CommonErr symconflict lea conf_mess,a1 jmp CommonErr Odd_addr lea odd_mess,a1 jmp CommonErr unknown lea un_mess,a1 jmp Err_char oplen_error lea lenerrmess,a1 jmp CommonErr mask_err lea mask_errmes,a1 jmp CommonErr page tables ******************************************************************************* * This table is used to create the length field for the generic MOVE ,* * instruction. It has a screwy length mapping, which this table achieves. * ******************************************************************************* fab_table dc.b $40 byte length (0) -> $40 dc.b $C0 word length (1) -> $C0 dc.b $80 long length (2) -> $80 dc.b $00 short length (3) -> $00 (no good) dc.b $C0 no spec. (4) -> $C0 dc.w 0 make sure table starts on word boundary ****************************************************************************** * The table format is the following: * * nn+0 through nn+5 : ASCII form of mnemonic, padded with spaces * * nn+6 through nn+9 : a 32-bit value parameter, usually the opcode * * nn+10 through nn+13 : the address of an assembly routine * * The end of table is marked by a $00000000 value. * ****************************************************************************** op_table equ * dc.b 'ABCD ' dc.l $C100 dc.l Azm_xBCD dc.b 'ADD ' dc.l $D650 dc.l Azm_ADSB dc.b 'ADDA ' dc.l $D650 dc.l Azm_ASA dc.b 'ADDI ' dc.l $D650 dc.l Azm_ASI dc.b 'ADDQ ' dc.l $D650 dc.l Azm_ASQ dc.b 'ADDX ' dc.l $D100 dc.l Azm_opX dc.b 'AND ' dc.l $C002 dc.l Azm_ANDOR dc.b 'ANDI ' dc.l $C002 dc.l Azm_ANDORI dc.b 'ASL ' dc.l $E1C0 dc.l Azm_shift dc.b 'ASR ' dc.l $E0C0 dc.l Azm_shift dc.b 'BCC ' dc.l $6400 dc.l Azm_Bxx dc.b 'BCS ' dc.l $6500 dc.l Azm_Bxx dc.b 'BEQ ' dc.l $6700 dc.l Azm_Bxx dc.b 'BGE ' dc.l $6C00 dc.l Azm_Bxx dc.b 'BGT ' dc.l $6E00 dc.l Azm_Bxx dc.b 'BHI ' dc.l $6200 dc.l Azm_Bxx dc.b 'BLE ' dc.l $6F00 dc.l Azm_Bxx dc.b 'BLS ' dc.l $6300 dc.l Azm_Bxx dc.b 'BLT ' dc.l $6D00 dc.l Azm_Bxx dc.b 'BMI ' dc.l $6B00 dc.l Azm_Bxx dc.b 'BNE ' dc.l $6600 dc.l Azm_Bxx dc.b 'BPL ' dc.l $6A00 dc.l Azm_Bxx dc.b 'BVC ' dc.l $6800 dc.l Azm_Bxx dc.b 'BVS ' dc.l $6900 dc.l Azm_Bxx dc.b 'BCHG ' dc.l $0040 dc.l Azm_Bitop dc.b 'BCLR ' dc.l $0080 dc.l Azm_Bitop dc.b 'BRA ' dc.l $6000 dc.l Azm_Bxx dc.b 'BSET ' dc.l $00C0 dc.l Azm_Bitop dc.b 'BSR ' dc.l $6100 dc.l Azm_BSR dc.b 'BTST ' dc.l $0000 dc.l Azm_Bitop dc.b 'CHK ' dc.l $4180 dc.l Azm_CHK dc.b 'CLR ' dc.l $4200 dc.l Azm_monop dc.b 'CMP ' dc.l 0 dummy value dc.l Azm_CMP dc.b 'CMPA ' dc.l 0 dummy value dc.l Azm_CMPA dc.b 'CMPI ' dc.l 0 dummy value dc.l Azm_CMPI dc.b 'CMPM ' dc.l 0 dummy value dc.l Azm_CMPM dc.b 'DBCC ' dc.l $54C8 dc.l Azm_DBxx dc.b 'DBCS ' dc.l $55C8 dc.l Azm_DBxx dc.b 'DBEQ ' dc.l $57C8 dc.l Azm_DBxx dc.b 'DBF ' dc.l $51C8 dc.l Azm_DBxx dc.b 'DBRA ' same as DBF dc.l $51C8 dc.l Azm_DBxx dc.b 'DBGE ' dc.l $5CC8 dc.l Azm_DBxx dc.b 'DBGT ' dc.l $5EC8 dc.l Azm_DBxx dc.b 'DBHI ' dc.l $52C8 dc.l Azm_DBxx dc.b 'DBLE ' dc.l $5FC8 dc.l Azm_DBxx dc.b 'DBLS ' dc.l $53C8 dc.l Azm_DBxx dc.b 'DBLT ' dc.l $5DC8 dc.l Azm_DBxx dc.b 'DBMI ' dc.l $5BC8 dc.l Azm_DBxx dc.b 'DBNE ' dc.l $56C8 dc.l Azm_DBxx dc.b 'DBPL ' dc.l $5AC8 dc.l Azm_DBxx dc.b 'DBT ' dc.l $50C8 dc.l Azm_DBxx dc.b 'DBVC ' dc.l $58C8 dc.l Azm_DBxx dc.b 'DBVS ' dc.l $59C8 dc.l Azm_DBxx dc.b 'DIVS ' dc.l $81C0 dc.l Azm_MULDIV dc.b 'DIVU ' dc.l $80C0 dc.l Azm_MULDIV dc.b 'EOR ' dc.l $B100 dc.l Azm_EOR dc.b 'EORI ' dc.l 0 dummy value dc.l Azm_EORI dc.b 'EXG ' dc.l $C140 dc.l Azm_EXG dc.b 'EXT ' dc.l $4880 dc.l Azm_EXT dc.b 'JMP ' dc.l $4EC0 dc.l Azm_JMP dc.b 'JSR ' dc.l $4E80 dc.l Azm_JSR dc.b 'LEA ' dc.l $41C0 dc.l Azm_LEA dc.b 'LINK ' dc.l $4E50 dc.l Azm_LINK dc.b 'LSL ' dc.l $E3C8 dc.l Azm_shift dc.b 'LSR ' dc.l $E2C8 dc.l Azm_shift dc.b 'MOVE ' dc.l 0 dummy value dc.l Azm_MOVE dc.b 'MOVEA ' dc.l 0 dummy value dc.l Azm_MOVEA dc.b 'MOVEM ' dc.l $4880 dc.l Azm_MOVEM dc.b 'MOVEP ' dc.l 0 dummy value dc.l Azm_MOVEP dc.b 'MOVEQ ' dc.l 0 dummy value dc.l Azm_MOVEQ dc.b 'MULS ' dc.l $C1C0 dc.l Azm_MULDIV dc.b 'MULU ' dc.l $C0C0 dc.l Azm_MULDIV dc.b 'NBCD ' dc.l $4800 dc.l Azm_NBCD dc.b 'NEG ' dc.l $4400 dc.l Azm_negs dc.b 'NEGX ' dc.l $4000 dc.l Azm_negs dc.b 'NOP ' dc.l $4E71 dc.l Azm_noop dc.b 'NOT ' dc.l $4600 dc.l Azm_negs dc.b 'OR ' dc.l $8000 dc.l Azm_ANDOR dc.b 'ORI ' dc.l $8000 dc.l Azm_ANDORI dc.b 'PEA ' dc.l $4840 dc.l Azm_PEA dc.b 'RESET ' dc.l $4E70 dc.l Azm_noop dc.b 'ROL ' dc.l $E7D8 dc.l Azm_shift dc.b 'ROR ' dc.l $E6D8 dc.l Azm_shift dc.b 'ROXL ' dc.l $E5D0 dc.l Azm_shift dc.b 'ROXR ' dc.l $E4D0 dc.l Azm_shift dc.b 'RTE ' dc.l $4E73 dc.l Azm_noop dc.b 'RTR ' dc.l $4E77 dc.l Azm_noop dc.b 'RTS ' dc.l $4E75 dc.l Azm_noop dc.b 'SCC ' dc.l $54C0 dc.l Azm_Sxx dc.b 'SCS ' dc.l $55C0 dc.l Azm_Sxx dc.b 'SEQ ' dc.l $57C0 dc.l Azm_Sxx dc.b 'SF ' dc.l $51C0 dc.l Azm_Sxx dc.b 'SGE ' dc.l $5CC0 dc.l Azm_Sxx dc.b 'SGT ' dc.l $5EC0 dc.l Azm_Sxx dc.b 'SHI ' dc.l $52C0 dc.l Azm_Sxx dc.b 'SLE ' dc.l $5FC0 dc.l Azm_Sxx dc.b 'SLS ' dc.l $53C0 dc.l Azm_Sxx dc.b 'SLT ' dc.l $5DC0 dc.l Azm_Sxx dc.b 'SMI ' dc.l $5BC0 dc.l Azm_Sxx dc.b 'SNE ' dc.l $56C0 dc.l Azm_Sxx dc.b 'SPL ' dc.l $5AC0 dc.l Azm_Sxx dc.b 'ST ' dc.l $50C0 dc.l Azm_Sxx dc.b 'SVC ' dc.l $58C0 dc.l Azm_Sxx dc.b 'SVS ' dc.l $59C0 dc.l Azm_Sxx dc.b 'SBCD ' dc.l $8100 dc.l Azm_xBCD dc.b 'STOP ' dc.l $4E72 dc.l Azm_STOP dc.b 'SUB ' dc.l $9451 dc.l Azm_ADSB dc.b 'SUBA ' dc.l $9451 dc.l Azm_ASA dc.b 'SUBI ' dc.l $9451 dc.l Azm_ASI dc.b 'SUBQ ' dc.l $9451 dc.l Azm_ASQ dc.b 'SUBX ' dc.l $9100 dc.l Azm_opX dc.b 'SWAP ' dc.l $4840 dc.l Azm_SWAP dc.b 'TAS ' dc.l $4AC0 dc.l Azm_TAS dc.b 'TRAP ' dc.l $4E40 dc.l Azm_TRAP dc.b 'TRAPV ' dc.l $4E76 dc.l Azm_noop dc.b 'TST ' dc.l $4000 dc.l Azm_monop dc.b 'UNLK ' dc.l $4E58 dc.l Azm_UNLK * END OF TABLE dc.w $0000 end of table ttl 'M68000 assembler --- storage' page storage sect RamVars table_ptr ds.l 1 op_buff ds.w opbufflen/2 opbufflen must be even Operand_len ds.b 1 EA_type ds.w 1 effective address type EA_ext ds.l 1 to hold extension word EA_field ds.b 1 the 6 bit ea field of the instruction src_type ds.w 1 effective address type src_ext ds.l 1 to hold extension word src_field ds.b 1 the 6 bit ea field of the instruction dst_type ds.w 1 effective address type dst_ext ds.l 1 to hold extension word dst_field ds.b 1 the 6 bit ea field of the instruction