X-Git-Url: http://cloudbase.mooo.com/gitweb/ddt180.git/blobdiff_plain/998c0841e630a26996601f9e5f4400f28f1512d4..c0b1aafa205f63cfe484290b624af9238399769b:/ddt180.z80 diff --git a/ddt180.z80 b/ddt180.z80 index f8b82b8..20d7a14 100644 --- a/ddt180.z80 +++ b/ddt180.z80 @@ -6,26 +6,8 @@ ; - Use Digital Research Link-80 to generate a .PRL file (op switch). ; - Cut the .PRL header (first 256 byte) end rename the result to DDTZ.COM. -;------------------------------------------------------------------------------- -; Relocation loader -; -TPA equ 0100h - cseg - .phase TPA - - jp start - ds 3 -ldr_end: -ldr_size equ $ - TPA -current_phase defl $ - - .dephase -current_cseg defl $ - -;------------------------------------------------------------------------------- -; DDT/Z core -; + maclib config.inc ; Some greneral definitions @@ -41,147 +23,456 @@ CNTRX equ 'X'-'@' BDOS equ 5 TPA equ 0100h -; BDOS function calls - -BDOS_PSTR equ 9 ;Print String - ; ddtz specific definitions STACK_SIZE equ 80 ;ddtz internal stack CONBUF_SIZE equ 80 ;Size of console input buffer -EXPR_BUF_SIZE equ 128 ;expressen buffer for conditional breakpoints BP_CNT equ 12 ;Number of breakpoints BP_SIZE equ 4 ;Size of a breakpoint record +bitmap_size equ (prog_size+7)/8 + ;------------------------------------------------------------------------------- -ddtz_base: - jp ddtz_bdos + cseg +start:: +ddtz_base:: + jr reloc + nop l0003h: - rst 30h -di_or_ei: + rst 30h ;rst used by ddtz +di_or_ei: ;ints enabled/disabled while ddtz is running nop ret -ddtz_bdos: - jp 0 -current_cseg defl $ - current_cseg - .phase current_phase + current_cseg +;------------------------------------------------------------------------------- + signon: db 'DDTZ/180' db ' - Version ' maclib version.inc defvers - db CR,LF,'$' -msgz80: - db 'Z80 or better required!',cr,lf,'$' + dc ' (' -current_phase defl $ - .dephase -current_cseg defl $ - ds STACK_SIZE - (current_phase - signon) +;------------------------------------------------------------------------------- +; Clear old position +cmde_clr: + ld (hl),0 + inc hl + dec bc + ld a,b + or c + jr nz,cmde_clr -stack: -reg.l2: db 000h -reg.h2: db 000h -reg.e2: db 000h -reg.d2: db 000h -reg.c2: db 000h -reg.b2: db 000h -reg.f2: db 000h -reg.a2: db 000h - db 000h -reg.i: db 000h -reg.iy: dw 0000h -reg.ix: dw 0000h -reg.f: db 000h -reg.a: db 000h -reg.c: db 000h -reg.b: db 000h -reg.e: db 000h -reg.d: db 000h -reg.l: db 000h -reg.h: db 000h -reg_sp: dw TPA -reg.iff: - db 0f3h - db 0c3h -reg.pc: dw TPA +; Determine current position -cmd_rpt:dw mainloop +reloc: + ld bc,(028h-2) + ld de,(028h) + ld a,i ;get iff2 + ex af,af' + di + ld sp,028h ;rst instr needs a minimal stack + ld hl,0e9e1h ;opcpdes pop hl/jp (hl) + ld (028h),hl + rst 028h +wearehere: + ld (028h-2),bc + ld (028h),de + ld de,-(wearehere-ddtz_base) + add hl,de ; hl: + + ld de,ddtz_base ; de: + or a + sbc hl,de + ex de,hl ; de: reloc offset + ld hl,stack + add hl,de + ld sp,hl + ex af,af' + push af + pop bc + bit 2,c + jr z,$+3 + ei + ld hl,ddtz_end ;start of reloc bitmap + add hl,de + + push hl + exx + pop hl + ld bc,0108h ;init bit counter b (c==reload val) + exx + + LD HL,ddtz_base + add hl,de ;--> ddtz_base + ld bc,prog_size +reloc_lp: + EXX + djnz reloc_nl + ld b,c ;reload bit counter + LD e,(HL) ;get next 8 relocation bits + INC HL +reloc_nl: + sla e + EXX + JR NC,reloc_next + DEC HL + LD A,(HL) + ADD A,E + LD (HL),A + INC HL + LD A,(HL) + ADC A,D + LD (HL),A +reloc_next: + inc hl + dec bc + ld a,b + or c + jr nz,reloc_lp ;------------------------------------------------------------------------------- -conbuf: - db CONBUF_SIZE - ld sp,stack - exx - ld de,ddtz_base - call cp_hl_de - jr c,l0079h - ex de,hl -l0079h: - ld de,TPA -l007ch: - dec hl - ld (hl),000h - ld a,h - sub d - ld b,a - ld a,l - sub e - or b - jr nz,l007ch - ld a,i - ld (reg.i),a - ld a,0f3h - jp po,l0093h - ld a,0fbh -l0093h: - ld (reg.iff),a - call di_or_ei - ld hl,ddtz_base - ld l,000h - ld (reg_sp),hl +init:: + LD SP,stack - ld hl,(1) ;wboot addr - ld de,?const - ld b,6 -vini_l: - inc hl - inc hl - inc hl + if CPM + + ld hl,(1) ;wboot addr + ld de,convec ex de,hl + ld b,3 +vini_l: + inc de + inc de + inc de inc hl ld (hl),e inc hl ld (hl),d inc hl - ex de,hl djnz vini_l + else + xor a + dec a + daa ; Z80: 099H, x180+: 0F9H + cp 99h ; Result on 180 type cpus is F9 here. Thanks Hitachi + jr z,ini_z80 + + xor a + call cinit + ld a,1 + call cinit + jr ini_sign +ini_z80: +; if ... +; .printx Error: Not yet implemented! +; db "Stop +; endif + endif ; CPM + +ini_sign: + ld hl,signon + call pstr + ld hl,ddtz_base + call out_hl + call pstr_inl + dc ' - ' + ld de,prog_size+bitmap_size-1 + add hl,de + call out_hl + call pstr_inl + dc ')',CR,LF + + ld a,i + ld (reg.i),a + ld a,0f3h + jp po,l0093h + ld a,0fbh +l0093h: + ld (reg.iff),a + call di_or_ei + ld hl,ddtz_base + ld l,000h + ld (reg_sp),hl + + jp mainloop + +;------------------------------------------------------------------------------- + + if CPM + +convec: +const: jp 0 ; return console input status +conin: jp 0 ; return console input character +conout: jp 0 ; send console output character + + else + + include z180reg.inc + +iobyte equ 3 + +max_device equ 3 + +;------------------------------------------------------------------------------- + +; init device +cinit: ; a = device + call vector_io_0 + dw as0init + dw rret + dw rret + dw rret + +; character input status +const: ; return a != 0 if character waiting + call vector_io + dw as0ista + dw null$status + dw csio_ista + dw null$status + +; character input +conin: ; return a = input char + call vector_io + dw as0inp + dw null$input + dw csio_inp + dw null$input + +; character output +conout: ; c = output char + call vector_io + dw as0out + dw rret + dw csio_out + dw rret + +;------------------------------------------------------------------------------- - jr mainloop +vector_io: + ld a,(iobyte) +vector_io_0: + pop hl + cp max_device + jr c,exist + ld a,max_device ; use null device if a >= max$device +exist: + call add_hl_a2 + ld a,(hl) + inc hl + ld h,(hl) + ld l,a + jp (hl) + +;------------------------------------------------------------------------------- + +null$input: + ld a,1Ah +rret: + ret +ret$true: + or 0FFh + ret + +null$status: + xor a + ret + +;------------------------------------------------------------------------------- +; +; TC = (f PHI /(2*baudrate*Clock_mode)) - 2 +; +; TC = (f PHI / (32 * baudrate)) - 2 +; +; Init Serial I/O for console input and output (ASCI1) +; + + + +as0init: + ld hl,initab0 + jp ioiniml + +as1init: + ld hl,initab1 + jp ioiniml + + + ld a,M_MPBT + out0 (cntlb1),a + ld a,M_RE + M_TE + M_MOD2 ;Rx/Tx enable + out0 (cntla1),a + ld a,M_RIE + out0 (stat1),a ;Enable rx interrupts + + ret ; + + +initab0: + db 1,stat0,0 ;Disable rx/tx interrupts + ;Enable baud rate generator + db 1,asext0,M_BRGMOD+M_DCD0DIS+M_CTS0DIS + db 2,astc0l,low 28, high 28 + db 1,cntlb0,M_MPBT ;No MP Mode, X16 + db 1,cntla0,M_RE+M_TE+M_MOD2 ;Rx/Tx enable, 8N1 + db 0 + +initab1: + db 1,stat1,0 ;Disable rx/tx ints, disable CTS1 + db 1,asext1,M_BRGMOD ;Enable baud rate generator + db 2,astc1l,low 3, high 3 + db 1,cntlb1,M_MPBT ;No MP Mode, X16 + db 1,cntla1,M_RE+M_TE+M_MOD2 ;Rx/Tx enable, 8N1 + db 0 + +;------------------------------------------------------------------------------- + +ioiniml: + push bc + xor a +ioml_lp: + ld b,(hl) + inc hl + cp b + jr z,ioml_e + + ld c,(hl) + inc hl + otimr + jr ioml_lp +ioml_e: + pop bc + ret + +;------------------------------------------------------------------------------- + +as0ista: + in0 a,(stat0) + rlca + sbc a,a + ret - ds CONBUF_SIZE + 3 - ($ - conbuf) +as1ista: + in0 a,(stat1) + rlca + sbc a,a + ret + +as0inp: + in0 a,(stat0) + rlca + jr nc,as0inp + in0 a,rdr0 + ret + +as1inp: + in0 a,(stat1) + rlca + jr nc,as1inp + in0 a,rdr1 + ret + +as0out: + in0 a,(stat0) + and M_TDRE + jr z,as0out + out0 (tdr0),c + ld a,c + ret + +as1out: + in0 a,(stat1) + and M_TDRE + jr z,as1out + out0 (tdr1),c + ld a,c + ret ;------------------------------------------------------------------------------- -?const: jp 0 ; return console input status -?conin: jp 0 ; return console input character -?cono: jp 0 ; send console output character -?list: jp 0 ; send list output character -?auxo: jp 0 ; send auxiliary output character -?auxi: jp 0 ; return auxiliary input character -CMDTAB: - dw ERROR ;cmd_@ ;examine/substitute the displacement register @ - dw ERROR ;cmd_A ;Assemble +csio_rx_tmp: db 0ffh + +csio_ista: + ld hl,csio_rx_tmp + ld a,(hl) + cp 0ffh + jr nz,csist_1 + ld a,01 + call csio_wr + call csio_rd + call csio_rd + ld (hl),a + sub a,0ffh + ret z +csist_1: + or 0ffh + ret + +csio_inp: + ld hl,csio_rx_tmp + ld a,(hl) + ld (hl),0ffh + cp 0ffh + ret nz +csin_1: + ld a,01 + call csio_wr + call csio_rd + call csio_rd + cp 0ffh + jr z,csin_1 + ret + +csio_rd: + ld a,M_CSIO_RE + call csio_cmd_wait + in0 a,(trdr) + ret + +csio_out: + ld a,02 + call csio_wr + call csio_rd + call csio_rd + or a + jr z,csio_out + + ld a,c + inc a ;ff..02 --> 00..03 + cp 04h + jr nc,csout_1 + ld a,00h + call csio_wr +csout_1: + ld a,c +csio_wr: + out0 (trdr),a + ld a,M_CSIO_TE +csio_cmd_wait: + out0 (cntr),a +cswr_wait: + in0 a,(cntr) + and M_CSIO_TE+M_CSIO_RE + jr nz,cswr_wait + ret + + endif ; CPM + +;------------------------------------------------------------------------------- + +CMDTAB:: +; dw ERROR ;cmd_@ ;examine/substitute the displacement register @ +; dw ERROR ;cmd_A ;Assemble dw cmd_B ;Breakpoints display/set/clear dw ERROR ;cmd_C ;trace over Calls dw cmd_D ;Display memory in hex and ascii - dw ERROR ; + dw cmd_E ;rElocate debugger dw ERROR ;cmd_F ;specify Filename and command line dw cmd_G ;Go dw cmd_H ;compute Hex and other expressions @@ -208,7 +499,7 @@ ERROR: call pstr_inl dc '?',CR,LF ;fall thru -mainloop: +mainloop:: ld sp,stack ld hl,(reg.pc) call bp_clr_temporary @@ -227,7 +518,7 @@ mainloop: push hl ld (cmd_rpt),hl inc de - sub '@' + sub 'B' jr c,ERROR cp 'Z'+1-'@' jr nc,ERROR @@ -255,8 +546,7 @@ crlf: sub_01d9h: call pstr_inl dc '-' - dec hl - jp cpl.hl + jp neg.hl out_hl_dec_neg: push hl @@ -323,9 +613,8 @@ out.bin.b: l01c9h: rlca push af - ld a,'0'/2 - adc a,a - call outchar + and 1 + call out_dgt pop af djnz l01c9h ld a,'"' @@ -376,7 +665,7 @@ outchar: push af and 07fh ld c,a - call ?cono + call conout ld hl,con_col inc (hl) pop af @@ -387,29 +676,6 @@ outchar: pop ix ret -pstr_sel: - inc b - jr pstr_sel2 -pstr_sel1: - call sub_0345h -pstr_sel2: - djnz pstr_sel1 - ;fall thru -pstr: - ld a,(hl) - inc hl - and a - ret z - call outchar - ret m - jr pstr - -pstr_inl: - ex (sp),hl - call pstr - ex (sp),hl - ret - p_goto_col: ld a,(con_col) cp c @@ -432,10 +698,10 @@ inchar: push hl push de push bc - call ?const + call const and a jr z,inch1 - call ?conin + call conin scf inch1: pop bc @@ -453,7 +719,6 @@ DELC: call DELC1 dec hl dec b - inc c ld a,(hl) cp ' ' ret nc @@ -474,13 +739,10 @@ DELL: get_line: push hl ; ld hl,conbuf ; - ld c,(hl) ; - inc hl ; - ld b,000h ; - inc hl ; + ld b,0 ; inlnxtch: - ld a,c ; - or a ; + ld a,b ; + cp CONBUF_SIZE ; jr z,inl_e ; call incharw ; cp CR ; @@ -516,16 +778,12 @@ gl_5: call outchar ; inc hl ; inc b ; - dec c ; jr inlnxtch ; inl_e: ld (hl),0 - ld hl,conbuf+1 ; - ld (hl),b ; call CRLF ; - inc hl - ex de,hl + ld de,conbuf ; pop hl ; ret ; @@ -653,14 +911,23 @@ l031eh: pop bc ret l0336h: - call sub_0345h + call str_sel_next l0339h: pop de and a pop bc ret -sub_0345h: +str_sel: + inc b + jr str_sel2 +str_sel1: + call str_sel_next +str_sel2: + djnz str_sel1 + ret + +str_sel_next: ld a,(hl) and a ret z @@ -671,12 +938,12 @@ l0348h: ret m jr l0348h -sub_034eh: +get_arg_range_target: call get_arg_range push hl push bc call next_arg - call sub_0363h + call get_arg_final ex de,hl pop bc pop hl @@ -687,7 +954,7 @@ sub_035dh: jr c,error0 ret -sub_0363h: +get_arg_final: call sub_035dh l0366h: jp assert_eol @@ -951,6 +1218,9 @@ do_factor: ld hl,TPA cp 'L' ret z + ld hl,(reg.pc) + cp '$' + ret z cp '-' jr z,fact_factneg cp '~' @@ -1009,8 +1279,13 @@ fact_reg.CPU: ld h,000h ret +fact_factinv: + call fact_factor + jr cpl.hl + fact_factneg: call fact_factor +neg.hl: dec hl cpl.hl: ld a,h @@ -1021,10 +1296,6 @@ cpl.hl: ld l,a ret -fact_factinv: - call fact_factor - jr cpl.hl - fact_mem: call expr1 jr c,error1 @@ -1303,17 +1574,60 @@ b_0709_start: db 000h ;------------------------------------------------------------------------------- -; > G [startaddr] [;breakp..] -; Go [to start] [with temporary breakpoints] +; > E addr +; relocate debugger to addr +; > ER addr +; relocate just below addr +; +; Move debugger to given address and restart. +; New location must not overlap with current location. -cmd_G: - sub a - ld (bp_p_cpu_flag),a - call expr - jr c,l0740h - ld (reg.pc),hl -l0740h: - call skipbl + +cmd_E: + call skipbl + sub 'R' + jr nz,$+3 + inc de + push af + call get_arg_final + + ld bc,prog_size+bitmap_size + pop af + jr nz,cmde_bottom + sbc hl,bc +cmde_bottom: + ld ix,cmde_clr-ddtz_base + ex de,hl ;de = dst + add ix,de + ld hl,ddtz_base ;hl = src + + push hl + or a + sbc hl,de + call c,neg.hl ;abs(distance) + or a + sbc hl,bc + jp c,error + pop hl + push hl + push bc + ldir + pop bc + pop hl + jp (ix) + +;------------------------------------------------------------------------------- +; > G [startaddr] [;breakp..] +; Go [to start] [with temporary breakpoints] + +cmd_G: + sub a + ld (bp_p_cpu_flag),a + call expr + jr c,l0740h + ld (reg.pc),hl +l0740h: + call skipbl jr z,user_go0 cp ';' jp nz,ERROR @@ -1691,7 +2005,7 @@ cmd_X: call get_line call skipbl jr z,l0c30h - call sub_0363h + call get_arg_final ex de,hl pop bc pop hl @@ -1963,11 +2277,11 @@ cmd_O: ret ;------------------------------------------------------------------------------- -; > Vstartaddr endaddr targetaddr +; > V startaddr endaddr targetaddr ; Verify (compare) two memory areas cmd_V: - call sub_034eh + call get_arg_range_target l0dedh: push bc ld a,(de) @@ -1999,7 +2313,7 @@ l0e10h: ; Move memory cmd_M: - call sub_034eh + call get_arg_range_target call cp_hl_de jr nc,cmdm_up add hl,bc @@ -2009,7 +2323,7 @@ cmd_M: dec hl dec de lddr - db 01h ;swallow ldir instruction (ld bc,...) + ret cmdm_up: ldir ret @@ -2108,9 +2422,9 @@ l0ed3h: ret sub_0ee6h: - ld hl,conbuf+1 + ld hl,conbuf call sub_0ef7h - ld de,conbuf+1 + ld de,conbuf and a sbc hl,de ld b,l @@ -2439,8 +2753,7 @@ p_disas_instr: ld c,a call pstr ;print mnemonic call p_goto_col - ex de,hl - call CALL_HL ;print arguments + call pr_instr_args ;print arguments pop bc scf ret @@ -2508,15 +2821,6 @@ disas_nopfx: disas_pfx.ED: inc iy - ld hl,b_1bc9_start ;1 byte opcode, no arguments - call lookup_op - ld b,2 - ret c - ld hl,b_1bf4_start - call lookup_op_arg - ld b,2 - ret c - ld hl,l228bh call lookup_op_arg ld b,3 @@ -2524,6 +2828,32 @@ disas_pfx.ED: ld hl,b_1c40_start call lookup_op_arg ld b,4 + ret c + + ld hl,b_1bc9_start ;1 byte opcode, no arguments + call lookup_op + jr c,da_ed1 + + ld hl,b_1bf4_start + call lookup_op_arg + ret nc + + ld a,e + cp a_noarg + jr nz,da_ed0 + ld c,(iy+0) + ld a,c + rra + and 0ch + ld b,a + ld a,c + and 03h + call str_sel_ab + +da_ed0: + scf +da_ed1: + ld b,2 ret ;------------------------------------------------------------------------------- @@ -2620,61 +2950,74 @@ l1a0ah: ;------------------------------------------------------------------------------- +test_DDFD: + ld a,(hl) + and a + ret z + inc hl + cp (iy+000h) + jr nz,test_DDFD + scf + ret + lookup_op: ld a,(hl) + inc hl cp 0ffh ret z cp (iy+000h) jr z,l1a7fh inc hl - inc hl jr lookup_op l1a7fh: - ld de,p_arg_none - inc hl - ld c,(hl) + ld b,(hl) + ld e,a_noarg jr get_mnemonic +lookup_op_arg: + call lookup_branch_op + ret nc + ld a,e + ld e,d + cp a,0ffh + ret z ;carry clear + ld b,a -test_DDFD: - ld a,(hl) - and a - ret z - inc hl - cp (iy+000h) - jr nz,test_DDFD +get_mnemonic: + ld hl,t_MNEMONICS + bit 7,b + jr z,get_m1 + res 7,b + ld a,(iy+000h) + rra + rra + rra + and 07h +str_sel_ab: + add b + ld b,a +get_m1: + call str_sel scf ret -lookup_op_arg: - ld a,(iy+000h) - and (hl) +lookup_branch_op ;TODO + ld a,(hl) + and a + ret z inc hl + and (iy+000h) cp (hl) - jr z,l1aa8h - inc hl inc hl + jr z,l1aa8_br inc hl inc hl - ld a,(hl) - and a - jr nz,lookup_op_arg - ret + jr lookup_branch_op -l1aa8h: - inc hl - ld c,(hl) - inc c - ret z - dec c - inc hl +l1aa8_br: ld e,(hl) inc hl ld d,(hl) -get_mnemonic: - ld hl,t_MNEMONICS - ld b,0 - add hl,bc scf ret @@ -2682,20 +3025,20 @@ get_mnemonic: ; 1 byte opcodes (no parameters) ; Format: db opcode, t_MNEMONICS-index b_1ab6_start: - db 076h,o_HALT ;halt - db 0d9h,o_EXX ;exx - db 0f3h,o_DI ;di - db 0fbh,o_EI ;ei - db 000h,o_NOP ;nop - db 007h,o_RLCA ;rlca - db 00fh,o_RRCA ;rrca - db 017h,o_RLA ;rla - db 01fh,o_RRA ;rra - db 027h,o_DAA ;daa - db 02fh,o_CPL ;cpl - db 037h,o_SCF ;scf - db 03fh,o_CCF ;ccf - db 0c9h,o_RET ;ret + db 076h,i_HALT ;halt + db 0d9h,i_EXX ;exx + db 0f3h,i_DI ;di + db 0fbh,i_EI ;ei + db 000h,i_NOP ;nop +; db 007h,i_RLCA ;rlca +; db 00fh,i_RRCA ;rrca +; db 017h,i_RLA ;rla +; db 01fh,i_RRA ;rra +; db 027h,i_DAA ;daa +; db 02fh,i_CPL ;cpl +; db 037h,i_SCF ;scf +; db 03fh,i_CCF ;ccf + db 0c9h,i_RET ;ret db 0ffh @@ -2703,303 +3046,425 @@ b_1ab6_start: ; Format: db mask, match, t_MNEMONICS-index ; dw argument formating function b_1ad1_start: - db 0c0h,040h,o_LD ;ld r[y],r[z] - dw p_arg_ry_rz - db 0f8h,080h,o_ADD ;add a,r[z] - dw p_arg_a_r - db 0f8h,088h,o_ADC ;adc a,r[z] - dw p_arg_a_r - db 0f8h,090h,o_SUB ;sub r[z] - dw p_rz - db 0f8h,098h,o_SBC ;sbc a,r[z] - dw p_arg_a_r - db 0f8h,0a0h,o_AND ;and r[z] - dw p_rz - db 0f8h,0a8h,o_XOR ;xor r[z] - dw p_rz - db 0f8h,0b0h,o_OR ;or r[z] - dw p_rz - db 0f8h,0b8h,o_CP ;cp r[z] - dw p_rz - db 0c7h,0c0h,o_RET ;ret cc - dw p_cc - db 0c7h,0c7h,o_RST ;rst - dw p_arg_rst - db 0cfh,0c1h,o_POP ;pop rp2 - dw p_rp2 - db 0cfh,0c5h,o_PUSH ;push rp2 - dw p_rp2 - db 0ffh,0e3h,o_EX ;ex (sp),hl - dw l1ca0h - db 0ffh,0e9h,o_JP ;jp (hl) - dw l1caeh - db 0ffh,0ebh,o_EX ;ex de,hl - dw p_arg_ex_dehl - db 0ffh,0f9h,o_LD ;ld sp,hl - dw l1cc1h - db 0cfh,003h,o_INC ;inc rp - dw p_rp - db 0cfh,00bh,o_DEC ;dec rp - dw p_rp - db 0c7h,004h,o_INC ;inc r[y] - dw p_ry - db 0c7h,005h,o_DEC ;dec r[y] - dw p_ry - db 0ffh,008h,o_EX ;ex af,af' - dw p_arg_ex_afaf - db 0cfh,009h,o_ADD ;add hl,rp - dw l1dcah - db 0efh,002h,o_LD ;ld (rp),a ;rp=bc,de - dw l1cdch - db 0efh,00ah,o_LD ;ld a,(rp) ;rp=bc,de - dw l1ce5h + db 0c0h,040h,i_LD ;ld r[y],r[z] + db a_rr + + db 0c0h,080h,i_ADD+080h ;add a,r[z] + db a_r + +; db 0f8h,080h,i_ADD ;add a,r[z] +; db a_ar +; db 0f8h,088h,i_ADC ;adc a,r[z] +; db a_ar +; db 0f8h,090h,i_SUB ;sub r[z] +; db a_r +; db 0f8h,098h,i_SBC ;sbc a,r[z] +; db a_ar +; db 0f8h,0a0h,i_AND ;and r[z] +; db a_r +; db 0f8h,0a8h,i_XOR ;xor r[z] +; db a_r +; db 0f8h,0b0h,i_OR ;or r[z] +; db a_r +; db 0f8h,0b8h,i_CP ;cp r[z] +; db a_r + + db 0c7h,0c0h,i_RET ;ret cc + db a_cc + db 0c7h,0c7h,i_RST ;rst + db a_rst + db 0cfh,0c1h,i_POP ;pop rp2 + db a_p2 + db 0cfh,0c5h,i_PUSH ;push rp2 + db a_p2 + db 0ffh,0e3h,i_EX ;ex (sp),hl + db a_esphl + db 0ffh,0e9h,i_JP ;jp (hl) + db a_hl + db 0ffh,0ebh,i_EX ;ex de,hl + db a_dehl + db 0ffh,0f9h,i_LD ;ld sp,hl + db a_lsphl + db 0cfh,003h,i_INC ;inc rp + db a_p + db 0cfh,00bh,i_DEC ;dec rp + db a_p + db 0c7h,004h,i_INC ;inc r[y] + db a_ry + db 0c7h,005h,i_DEC ;dec r[y] + db a_ry + db 0ffh,008h,i_EX ;ex af,af' + db a_eaf + db 0cfh,009h,i_ADD ;add hl,rp + db a_hlp + db 0efh,002h,i_LD ;ld (rp),a ;rp=bc,de + db a_pa + db 0efh,00ah,i_LD ;ld a,(rp) ;rp=bc,de + db a_ap + + db 0c7h,007h,i_RLCA+080h;rlca + db a_noarg + db 0 -; 2 byte opdodes +; 2 byte opcodes b_1b54_start: - db 0c7h,006h,o_LD ;ld r[y],nn - dw l1cfah - db 0ffh,0c6h,o_ADD ;add a,nn - dw l1cf5h - db 0ffh,0ceh,o_ADC ;adc a,nn - dw l1cf5h - db 0ffh,0d6h,o_SUB ;sub nn - dw l1d09h - db 0ffh,0deh,o_SBC ;sbc a,nn - dw l1cf5h - db 0ffh,0e6h,o_AND ;and nn - dw l1d09h - db 0ffh,0eeh,o_XOR ;xor nn - dw l1d09h - db 0ffh,0f6h,o_OR ;or nn - dw l1d09h - db 0ffh,0feh,o_CP ;cp nn - dw l1d09h - db 0ffh,010h,o_DJNZ ;djnz - dw p_arg_jrel - db 0ffh,018h,o_JR ;jr - dw p_arg_jrel - db 0e7h,020h,o_JR ;jr cc, - dw p_arg_cc_jrel - db 0ffh,0d3h,o_OUT ;out (nn),a - dw l1d37h - db 0ffh,0dbh,o_IN ;in a,(nn) - dw l1d29h + db 0c7h,006h,i_LD ;ld r[y],nn + db a_rn + + db 0c7h,0c6h,i_ADD+080h ;add a,r[z] + db a_n + +; db 0ffh,0c6h,i_ADD ;add a,nn +; db a_an +; db 0ffh,0ceh,i_ADC ;adc a,nn +; db a_an +; db 0ffh,0d6h,i_SUB ;sub nn +; db a_n +; db 0ffh,0deh,i_SBC ;sbc a,nn +; db a_an +; db 0ffh,0e6h,i_AND ;and nn +; db a_n +; db 0ffh,0eeh,i_XOR ;xor nn +; db a_n +; db 0ffh,0f6h,i_OR ;or nn +; db a_n +; db 0ffh,0feh,i_CP ;cp nn +; db a_n + + db 0ffh,010h,i_DJNZ ;djnz + db a_j + db 0ffh,018h,i_JR ;jr + db a_j + db 0e7h,020h,i_JR ;jr cc, + db a_ccj + db 0ffh,0d3h,i_OUT ;out (nn),a + db a_ma + db 0ffh,0dbh,i_IN ;in a,(nn) + db a_am db 0 ; 3 byte opcodes b_1b9b_start: - db 0c7h,0c2h,o_JP ;jp cc,mn - dw p_arg_cc_mn - db 0c7h,0c4h,o_CALL ;call cc,mn - dw p_arg_cc_mn - db 0cfh,001h,o_LD ;ld ww,mn - dw p_arg_ww_mn - db 0ffh,0c3h,o_JP ;jp mn - dw p_arg_mn - db 0ffh,0cdh,o_CALL ;call mn - dw p_arg_mn - db 0ffh,022h,o_LD ;ld (mn),hl - dw p_arg_addr_hl - db 0ffh,02ah,o_LD ;ld hl,(mn) - dw p_arg_hl_addr - db 0ffh,032h,o_LD ;ld (mn),a - dw p_arg_addr_a - db 0ffh,03ah,o_LD ;ld a,(mn) - dw p_arg_a_addr + db 0c7h,0c2h,i_JP ;jp cc,mn + db a_ccnn + db 0c7h,0c4h,i_CALL ;call cc,mn + db a_ccnn + db 0cfh,001h,i_LD ;ld ww,mn + db a_rnn + db 0ffh,0c3h,i_JP ;jp mn + db a_nn + db 0ffh,0cdh,i_CALL ;call mn + db a_nn + db 0ffh,022h,i_LD ;ld (mn),hl + db a_mmhl + db 0ffh,02ah,i_LD ;ld hl,(mn) + db a_hlmm + db 0ffh,032h,i_LD ;ld (mn),a + db a_mma + db 0ffh,03ah,i_LD ;ld a,(mn) + db a_amm db 0 ; Prefix ED + 1 byte opcode, no arguments ; Format: opcode, t_MNEMONICS index b_1bc9_start: - db 044h,o_NEG ;neg - db 045h,o_RETN ;retn - db 04dh,o_RETI ;reti - db 067h,o_RRD ;rrd - db 06fh,o_RLD ;rld - db 0a0h,o_LDI ;ldi - db 0a1h,o_CPI ;cpi - db 0a2h,o_INI ;ini - db 0a3h,o_OUTI ;outi - db 0a8h,o_LDD ;ldd - db 0a9h,o_CPD ;cpd - db 0aah,o_IND ;ind - db 0abh,o_OUTD ;outd - db 0b0h,o_LDIR ;ldir - db 0b1h,o_CPIR ;cpir - db 0b2h,o_INIR ;inir - db 0b3h,o_OTIR ;otir - db 0b8h,o_LDDR ;lddr - db 0b9h,o_CPDR ;cpdr - db 0bah,o_INDR ;indr - db 0bbh,o_OTDR ;otdr - db 08bh,o_OTDM ;otdm - db 09bh,o_OTDMR ;otdmr - db 083h,o_OTIM ;otim - db 093h,o_OTIMR ;otimr - db 076h,o_SLP ;slp + db 044h,i_NEG ;neg + db 045h,i_RETN ;retn + db 04dh,i_RETI ;reti + db 067h,i_RRD ;rrd + db 06fh,i_RLD ;rld +; db 0a0h,i_LDI ;ldi +; db 0a1h,i_CPI ;cpi +; db 0a2h,i_INI ;ini +; db 0a3h,i_OUTI ;outi +; db 0a8h,i_LDD ;ldd +; db 0a9h,i_CPD ;cpd +; db 0aah,i_IND ;ind +; db 0abh,i_OUTD ;outd +; db 0b0h,i_LDIR ;ldir +; db 0b1h,i_CPIR ;cpir +; db 0b2h,i_INIR ;inir +; db 0b3h,i_OTIR ;otir +; db 0b8h,i_LDDR ;lddr +; db 0b9h,i_CPDR ;cpdr +; db 0bah,i_INDR ;indr +; db 0bbh,i_OTDR ;otdr + db 08bh,i_OTDM ;otdm + db 09bh,i_OTDMR ;otdmr + db 083h,i_OTIM ;otim + db 093h,i_OTIMR ;otimr + db 076h,i_SLP ;slp db 0ffh ; b_1bf4_start: - db 0ffh,070h,o_IN ;in (c) ; - dw p_arg_in_c_0 ; - db 0c7h,040h,o_IN ;in r,(c) ;r=b,c,d,e,h,l,a - dw p_arg_in_c ; + db 0e4h,0a0h,i_LDI + db a_noarg + db 0ffh,070h,i_IN ;in (c) ; + db a_c + db 0c7h,040h,i_IN ;in r,(c) ;r=b,c,d,e,h,l,a + db a_rc db 0ffh,071h,0ffh ;out (c),0 ; - dw p_arg_out_c ; - db 0c7h,041h,o_OUT ;out (c),r ;r=b,c,d,e,h,l,a - dw p_arg_out_c ; - db 0cfh,042h,o_SBC ;sbc hl,rp - dw l1dcah ; - db 0cfh,04ah,o_ADC ;adc hl,rp - dw l1dcah ; - db 0ffh,046h,o_IM ;im 0 - dw l1d85h ; - db 0ffh,056h,o_IM ;im 1 - dw l1d89h ; - db 0ffh,05eh,o_IM ;im 2 - dw l1d8dh ; - db 0e7h,047h,o_LD ;ld i,a ... ld a,r - dw p_arg_IR ; - db 0cfh,04ch,o_MLT ;mlt rr - dw p_rp - db 0c7h,004h,o_TST ;tst r - dw p_ry + db a_cr + db 0c7h,041h,i_OUT ;out (c),r ;r=b,c,d,e,h,l,a + db a_cr + db 0cfh,042h,i_SBC ;sbc hl,rp + db a_hlp + db 0cfh,04ah,i_ADC ;adc hl,rp + db a_hlp + db 0ffh,046h,i_IM ;im 0 + db a_im0 + db 0ffh,056h,i_IM ;im 1 + db a_im1 + db 0ffh,05eh,i_IM ;im 2 + db a_im2 + db 0e7h,047h,i_LD ;ld i,a ... ld a,r + db a_ai + db 0cfh,04ch,i_MLT ;mlt rr + db a_p + db 0c7h,004h,i_TST ;tst r + db a_ry db 0 l228bh: - db 0ffh,030h,0ffh ;in0 (m) - dw p_arg_r_m - db 0c7h,000h,o_IN0 ;in0 r,(m) ;r=b,c,d,e,h,l,a - dw p_arg_r_m + db 0ffh,030h,i_IN0 ;in0 (m) + db a_m + db 0c7h,000h,i_IN0 ;in0 r,(m) ;r=b,c,d,e,h,l,a + db a_rm db 0ffh,031h,0ffh ;out0 (m),0 - dw p_arg_m_r - db 0c7h,001h,o_OUT0 ;out0 (m),r ;r=b,c,d,e - dw p_arg_m_r - db 0ffh,064h,o_TST ;tst m - dw l1d09h - db 0ffh,074h,o_TSTIO ;tstio m - dw l1d09h + db a_mr + db 0c7h,001h,i_OUT0 ;out0 (m),r ;r=b,c,d,e + db a_mr + db 0ffh,064h,i_TST ;tst m + db a_n + db 0ffh,074h,i_TSTIO ;tstio m + db a_n db 0 ; Prefix ED + 1 byte opcode + 2 byte address ; Format: db mask, match, t_MNEMONICS-index ; dw argument formating function b_1c40_start: - db 0cfh,043h,o_LD ;ld (mn),ww ;ww=bc,de,hl,sp - dw p_arg_addr_ww - db 0cfh,04bh,o_LD ;ld ww,(mn) ;ww=bc,de,hl,sp - dw p_arg_ww_addr + db 0cfh,043h,i_LD ;ld (mn),ww ;ww=bc,de,hl,sp + db a_mmp + db 0cfh,04bh,i_LD ;ld ww,(mn) ;ww=bc,de,hl,sp + db a_pmm db 0 ; CB b_1c55_start: - db 0f8h,000h,o_RLC ;rlc g - dw p_rz_cb - db 0f8h,008h,o_RRC ;rrc g - dw p_rz_cb - db 0f8h,010h,o_RL ;rl g - dw p_rz_cb - db 0f8h,018h,o_RR ;rr g - dw p_rz_cb - db 0f8h,020h,o_SLA ;sla g - dw p_rz_cb - db 0f8h,028h,o_SRA ;sra g - dw p_rz_cb - db 0f8h,038h,o_SRL ;srl g - dw p_rz_cb - db 0c0h,040h,o_BIT ;bit b,g - dw p_arg_bitop - db 0c0h,080h,o_RES ;res b,g - dw p_arg_bitop - db 0c0h,0c0h,o_SET ;set b,g - dw p_arg_bitop + db 0c0h,000h,i_RLC+080h ;rlc g + db a_cbr + +; db 0f8h,000h,i_RLC ;rlc g +; db a_cbr +; db 0f8h,008h,i_RRC ;rrc g +; db a_cbr +; db 0f8h,010h,i_RL ;rl g +; db a_cbr +; db 0f8h,018h,i_RR ;rr g +; db a_cbr +; db 0f8h,020h,i_SLA ;sla g +; db a_cbr +; db 0f8h,028h,i_SRA ;sra g +; db a_cbr +; db 0f8h,038h,i_SRL ;srl g +; db a_cbr + db 0c0h,040h,i_BIT ;bit b,g + db a_bcbr + db 0c0h,080h,i_RES ;res b,g + db a_bcbr + db 0c0h,0c0h,i_SET ;set b,g + db a_bcbr db 0 ;------------------------------------------------------------------------------- +;------------------------------------------------------------------------------- -p_arg_ry_rz: - call p_ry - call p_char_comma - jp p_rz -p_arg_a_r: - call p_A_comma - jp p_rz -p_arg_r_m: - call p_ry - call p_char_comma - jp sub_1d2ch +pr_instr_args: + ld hl,t_argf + ld d,0 + add hl,de +pria_l: + ld a,(hl) ;get next token + inc hl + or a + ret z ; + jp m,pria_1 + call outchar ;print as normal character + jr pria_l -p_arg_m_r: - call sub_1d2ch - call p_char_comma - jp p_ry +pria_1: ; + push hl + ld hl,do_arg_n + and 07fh + call add_hl_a2 + ld a,(hl) + inc hl + ld h,(hl) + ld l,a + ld a,(iy+000h) + call CALL_HL + pop hl + jr pria_l -p_arg_rst: - ld a,(iy+000h) - and 038h - jp out_hex +; +; http://www.z80.info/decoding.htm +; +; | 7 | 6 | 5 | 4 | 3 | 2 | 1 | 0 | +; | x | y | z | +; | p | q | +; -l1ca0h: - call pstr_inl - DC '(SP),' - jp p_arg_hlixiy +t_argf: +; 1 byte opcodes +a_rr equ $-t_argf + db fi_ry,',' ;ld r[y],r[z] +a_r equ $-t_argf + db fi_rz,0 ;op r[z] +;a_ar equ $-t_argf +; db 'A,',fi_rz,0 ;op A,r[z] +a_cc equ $-t_argf + db fi_ccy,0 ;op cc[y] +a_rst equ $-t_argf + db fi_rst,0 ;rst y*8 +a_p2 equ $-t_argf + db fi_rp2,0 ;rp2[p] +a_esphl equ $-t_argf + db '(SP),',fi_hlixiy,0 ;ex (sp),hl +a_hl equ $-t_argf + db '(',fi_hlixiy,')',0 ;jp (hl) +a_dehl equ $-t_argf + db 'DE,HL',0 +a_lsphl equ $-t_argf + db 'SP,',fi_hlixiy,0 ;ld SP,HL +a_eaf equ $-t_argf + db 'AF,AF''',0 ;ex af,af' +a_hlp equ $-t_argf + db fi_hlixiy,',' ;add hl,rp +a_p equ $-t_argf + db fi_rp,0 ;rp[p] +a_pa equ $-t_argf + db '(',fi_rp,'),A',0 ;ld (rp),a ;rp=bc,de +a_ap equ $-t_argf + db 'A,(',fi_rp,')',0 ;ld a,(rp) ;rp=bc,de -l1caeh: - call p_char_lparen - call p_arg_hlixiy - jr out_rparen +; 2 byte opcodes +a_rn equ $-t_argf + db fi_ry,',',fi_n,0 ;ld r[y],n +;a_an equ $-t_argf +; db 'A,' ;op a,n +a_n equ $-t_argf + db fi_n,0 ;op n +a_ccj equ $-t_argf + db fi_ccy2,',' ;jr cc,j ;cc = nz,z,nc,c +a_j equ $-t_argf + db fi_j,0 ;jr j +a_ma equ $-t_argf + db '(',fi_n,'),A',0 ;out (n),a +a_am equ $-t_argf + db 'A,(',fi_n,')',0 ;in a,(n) + +; 3 byte opcodes +a_ccnn equ $-t_argf + db fi_ccy,',',fi_nn,0 ;op cc[y],nn +a_rnn equ $-t_argf + db fi_rp,',' ;ld rp[p],nn +a_nn equ $-t_argf + db fi_nn,0 ;jp nn +a_mmhl equ $-t_argf + db '(',fi_nn,'),',fi_hlixiy,0 ;ld (nn),hl +a_hlmm equ $-t_argf + db fi_hlixiy,',(',fi_nn,')',0 ;ld hl,(nn) +a_mma equ $-t_argf + db '(',fi_nn,'),A',0 ;ld (nn),a +a_amm equ $-t_argf + db 'A,(',fi_nn,')',0 ;ld a,(nn) -p_arg_ex_dehl: - call pstr_inl - DC 'DE,HL' -p_arg_none: - ret +; Prefix ED + 1 byte opcode +a_rc equ $-t_argf + db fi_ry,',' ;in r[y],(c) +a_c equ $-t_argf + db '(C)',0 ;in (c) +a_cr equ $-t_argf + db '(C),' ;out (c),r[y] +a_ry equ $-t_argf + db fi_ry,0 ;inc r[y] +a_im0 equ $-t_argf + db '0',0 ;im 0 +a_im1 equ $-t_argf + db '1',0 ;im 1 +a_im2 equ $-t_argf + db '2',0 ;im 2 +a_ai equ $-t_argf + db fi_ir,0 ;ld a,i ... r,a -l1cc1h: - call pstr_inl - DC 'SP,' - jp p_arg_hlixiy +; Prefix ED + 2 byte (opcode + immediate) +a_rm equ $-t_argf + db fi_ry,',' ;in0 r[y],(n) +a_m equ $-t_argf + db '(',fi_n,')',0 ;in0 (n) +a_mr equ $-t_argf + db '(',fi_n,'),',fi_ry,0 ;out0 (n),r[y] -p_arg_ex_afaf: - call pstr_inl - DC 'AF,AF''' - ret - -l1cdch: - call sub_1ce8h - call p_char_comma - jp p_char_A - -l1ce5h: - call p_A_comma -sub_1ce8h: - call p_char_lparen - call p_rp - jr out_rparen - -l1cf5h: - call p_A_comma - jr l1d09h -l1cfah: - call p_ry - call p_char_comma +; Prefix ED + 3 byte (opcode + address) +a_mmp equ $-t_argf + db '(',fi_nn,'),',fi_rp,0 ;ld (nn),rp +a_pmm equ $-t_argf + db fi_rp,',(',fi_nn,')',0 ;ld rp,(nn) + +; Prefix CB + 1 byte opcode +a_bcbr equ $-t_argf + db fi_y,',' ;op y,r[z] +a_cbr equ $-t_argf + db fi_rz_cb,0 ;op r[z] +a_noarg equ $-t_argf + db 0 + + +;------------------------------------------------------------------------------- + +argpf_index defl 0 + +argpf macro x +fi_&x equ 80h+argpf_index + dw p_&x +argpf_index defl argpf_index+1 + endm + +do_arg_n: + argpf ry + argpf rz + argpf ccy + argpf ccy2 + argpf rst + argpf rp + argpf rp2 + argpf hlixiy + argpf n + argpf j + argpf nn + argpf ir + argpf rz_cb + argpf y + + +p_n: ld a,(isprefix_ixiy) and a - ld a,(iy+002h) - jr nz,l1d0ch -l1d09h: ld a,(iy+001h) -l1d0ch: + jr z,out_hex_0 + ld a,(iy+002h) + jr out_hex_0 + +p_rst: + and 038h +out_hex_0: jp out_hex -p_arg_cc_jrel: - ld a,(iy+000h) - and 018h - call p_arg_cc0 - call p_char_comma -p_arg_jrel: + +p_j: ld c,(iy+001h) ld a,c rla @@ -3010,162 +3475,48 @@ p_arg_jrel: add hl,bc inc hl inc hl - jr l1d4eh + jr out_hl_0 -l1d29h: - call p_A_comma -sub_1d2ch: - call p_char_lparen - ld a,(iy+001h) -p_arg_nn_rp: - call out_hex -out_rparen: - jr p_char_rparen - -l1d37h: - call sub_1d2ch - jr p_char_comma_A - -p_arg_cc_mn: - call p_arg_cc - call p_char_comma -p_arg_mn: +p_nn: ld l,(iy+001h) ld h,(iy+002h) -l1d4eh: +out_hl_0: jp out_hl -p_arg_ww_mn: - call p_rp - call p_char_comma - jr p_arg_mn - -p_arg_addr_hl: - call p_arg_addr - call p_char_comma - jp p_arg_hlixiy - -p_arg_hl_addr: - call p_arg_hlixiy - call p_char_comma - jp p_arg_addr - -p_arg_addr_a: - call p_arg_addr -p_char_comma_A: - call p_char_comma - jr p_char_A - -p_A_comma: - call p_char_A -p_char_comma: - ld a,',' - db 021h -p_char_A: - ld a,'A' - db 021h -l1d85h: - ld a,'0' - db 021h -l1d89h: - ld a,'1' - db 021h -l1d8dh: - ld a,'2' - db 021h -p_char_rparen: - ld a,')' - db 021h -p_char_lparen: - ld a,'(' - jp outchar - -p_arg_IR: - ld a,(iy+000h) +p_ir: rra rra rra and 03 ld hl,t_arg_IR - jp p_arg + jr p_arg -t_arg_IR: - DC 'I,A' - DC 'R,A' - DC 'A,I' - DC 'A,R' - db 0 -p_arg_in_c: - call p_ry - call p_char_comma -p_arg_in_c_0: - ld hl,t__C_ - jp pstr +get_cb_opc: + ld a,(isprefix_ixiy) + and a + ld a,(iy+001h) + ret z + ld a,(iy+002h) + ret -p_arg_out_c: - ld hl,t__C_ - call pstr - call p_char_comma - jr p_ry - -l1dcah: - call p_arg_hlixiy - call p_char_comma - jp p_rp - -p_arg_addr_ww: - call p_arg_addr - call p_char_comma - jp p_rp - -p_arg_ww_addr: - call p_rp - call p_char_comma - jr p_arg_addr - -p_arg_a_addr: - call p_A_comma -p_arg_addr: - call p_char_lparen - call p_arg_mn - jr p_char_rparen - -p_arg_bitop: +p_y: call get_cb_opc - push af rra rra rra and 007h -; add a,'0' -; call outchar - call out_dgt - call p_char_comma - pop af - jr p_r0 + jp out_dgt p_rz_cb: call get_cb_opc - jr p_r0 - -get_cb_opc: - ld a,(isprefix_ixiy) - and a - ld a,(iy+001h) - ret z - ld a,(iy+002h) - ret + jr p_rz p_ry: - ld a,(iy+000h) rra rra rra - jr p_r0 p_rz: - ld a,(iy+000h) -p_r0: and 007h cp 006h ld b,a @@ -3189,39 +3540,30 @@ p_r0: l1e61h: call outchar pop af - jp p_arg_nn_rp - -t_lp_IXIY: - DC '(IX' - DC '(IY' - -p_arg_hlixiy: - ld a,(isprefix_ixiy) - ld hl,t_HL.IX.IY - jr p_arg + call out_hex + ld a,')' + jp outchar p_rp2: -p_arg_zz: ld hl,t_arg_rp2 - jr l1e8eh + db 0ddh ;swallow t_arg_rp in ix p_rp: -p_arg_ww: ld hl,t_arg_rp -l1e8eh: - ld a,(iy+000h) rra rra rra rra and 003h cp 002h - jr z,p_arg_hlixiy + jr nz,p_arg +p_hlixiy: + ld a,(isprefix_ixiy) + ld hl,t_HL.IX.IY jr p_arg -p_cc: -p_arg_cc: - ld a,(iy+000h) -p_arg_cc0: +p_ccy2: + and 018h +p_ccy: rra rra rra @@ -3230,51 +3572,42 @@ p_arg_cc0: p_arg: ld b,a p_arg0: - jp pstr_sel + ;fall thru -;------------------------------------------------------------------------------- +pstr_sel: + call str_sel + ;fall thru +pstr: + ld a,(hl) + inc hl + and a + ret z + call outchar + ret m + jr pstr -if 0 -p_bli: - ld a,(iy+000h) - rra - and 00ch - ld b,a - ld a,(iy+000h) - and 003h - or b - ld hl,t_mn_bli - jr p_arg -endif +pstr_inl: + ex (sp),hl + call pstr + ex (sp),hl + ret ;------------------------------------------------------------------------------- opc macro x i_&x equ opc_index -o_&x equ $-opc_tabstart +;o_&x equ $-opc_tabstart dc '&x' opc_index defl opc_index+1 endm -opc1 macro x,y - -i_&x&y equ opc_index -o_&x&y equ $-opc_tabstart - db '&x' -i_&y equ opc_index+1 -o_&y equ $-opc_tabstart - dc '&y' -opc_index defl opc_index+2 - endm - - t_MNEMONICS: -opc_tabstart defl $ +;opc_tabstart defl $ opc_index defl 0 ; 1-byte other opc NOP - opc1 R,LD + opc LD opc INC opc DEC opc DJNZ @@ -3296,8 +3629,8 @@ opc_index defl 0 opc SUB opc SBC opc AND -; opc XOR - opc1 X,OR + opc XOR + opc OR opc CP opc RET @@ -3310,17 +3643,17 @@ opc_index defl 0 opc EXX opc IN opc EX - opc1 L,DI + opc DI opc EI ; CB opc RLC opc RRC - opc1 S,RL + opc RL opc RR opc SLA opc SRA -; SLL -; opc SRL + opc SLL + opc SRL opc BIT opc RES opc SET @@ -3329,13 +3662,12 @@ opc_index defl 0 opc NEG opc RETN opc RETI - opc1 OT,IM + opc IM opc RRD -; opc RLD + opc RLD -;Block instructions -t_mn_bli: -; opc LDI +; Block instructions + opc LDI opc CPI opc INI opc OUTI @@ -3352,14 +3684,14 @@ t_mn_bli: opc INDR opc OTDR -;Z180 +; Z180 opc IN0 opc OUT0 opc TST opc MLT opc TSTIO opc SLP -; opc OTIM + opc OTIM opc OTDM opc OTIMR opc OTDMR @@ -3403,138 +3735,19 @@ t_arg_cc: DC 'P' DC 'M' DB 0 -t__C_: - DC '(C)' - DB 0 - -;------------------------------------------------------------------------------- -;------------------------------------------------------------------------------- -if 0 - -lookup_argstr: - ;todo - ret - - -pr_instr_args: - ld hl,t_argf - call lookup_argstr - - ret z - -pria_l: - ld a,(hl) ;get next token - inc hl - or a - ret z ; - jp m,pria_1 - call outchar ;print as normal character - jr pria_l - -pria_1: ; - push hl - ld hl,do_arg_n - and 07fh - call add_hl_a2 - ld a,(hl) - inc hl - ld h,(hl) - ld l,a - call CALL_HL - pop hl - jr pria_l - -; -; http://www.z80.info/decoding.htm -; -; | 7 | 6 | 5 | 4 | 3 | 2 | 1 | 0 | -; | x | y | z | -; | p | q | -; - -t_argf: - db fi_ry,',',fi_rz,0 ;ld r[y],r[z] - db 'A,',fi_rz,0 ;op A,r[z] - db fi_rz,0 ;op r[z] - db fi_ccy,0 ;op cc[y] - db fi_rst,0 ; - db fi_rp2,0 ;rp2[p] - db '(SP),',fi_hlixiy,0 ;ex (sp),hl - db fi_hlixiy,0 ;jp (hl) - db 'DE,HL',0 - db 'SP,',fi_hlixiy,0 ;ld SP,HL - db fi_rp,0 ;rp[p] - db fi_ry,0 ;inc r[y] - db 'AF,AF''',0 ;ex af,af' - db fi_hlixiy,fi_rp,0 ;add hl,rp - db '(',fi_rp,'),A',0 ;ld (rp),a ;rp=bc,de - db 'A,(',fi_rp,')',0 ;ld a,(rp) ;rp=bc,de - - db fi_ry,fi_n,0 ;ld r[y],n - db 'A,',fi_n,0 ;op a,n - db fi_n,0 ;op n - db fi_j,0 ;jr j - db fi_ccy2,fi_j,0 ;jr cc,j ;cc = nz,z,nc,c - db '(',fi_n,'),',fi_ry,0 ;out (n),a - db fi_ry,',(',fi_n,')',0 ;in a,(n) - - db fi_ccy,fi_nn,0 ;op cc[y],nn - db fi_rp,fi_nn,0 ;ld rp[p],nn - db fi_nn,0 ;jp nn - db '(',fi_nn,'),',fi_hlixiy,0 ;ld (nn),hl - db fi_hlixiy,',(',fi_nn,')',0 ;ld hl,(nn) - db '(',fi_nn,'),A',0 ;ld (nn),a - db 'A,(',fi_nn,')',0 ;ld a,(nn) - - db fi_ry,'(C)',0 ;in r[y],(c) - db '(C)',0 ;in (c) - db '(C)',fi_ry,0 ;out (c),r[y] - db '0',0 ;im 0 - db '1',0 ;im 1 - db '2',0 ;im 2 - db fi_ir,0 ;ld a,i ... r,a - - db fi_ry,'(',fi_n,')',0 ;in0 r[y],(n) - db '(',fi_n,')',0 ;in0 (n) - db '(',fi_n,')',fi_ry,0 ;out0 (n),r[y] - - db '(',fi_nn,'),',fi_rp,0 ;ld (nn),rp - db fi_rp,',(',fi_nn,')',0 ;ld rp,(nn) - - db fi_rz_cb,0 ;op r[z] - db fi_y,',',fi_rz_cb,0 ;op y,r[z] - - -;------------------------------------------------------------------------------- - -argpf_index defl 0 - -argpf macro x -fi_&x equ 80h+argpf_index - dw p_&x -argpf_index defl argpf_index+1 - endm -do_arg_n: - argpf ry - argpf rz - argpf m8 - argpf rst - argpf hlixiy - argpf rp - argpf rp2 +t_lp_IXIY: + DC '(IX' + DC '(IY' -p_ry: -p_rz: -p_m8: -p_rst: -p_hlixiy: -p_rp: -p_rp2: +t_arg_IR: + DC 'I,A' + DC 'R,A' + DC 'A,I' + DC 'A,R' + db 0 -endif -;------------------------------------------------------------------------------- ;------------------------------------------------------------------------------- tc_set_bp: @@ -3557,7 +3770,7 @@ tc_set_bp: call bp_trace_enter ld iy,(reg.pc) ld hl,t_op_branch - call lookup_op_arg + call lookup_branch_op ccf ret c ex de,hl @@ -3571,34 +3784,34 @@ l2037h: ;------------------------------------------------------------------------------- t_op_branch: - db 0ffh,0ddh,0 ;Prefix DD + db 0ffh,0ddh ;Prefix DD dw l20a7h - db 0ffh,0fdh,0 ;Prefix FD + db 0ffh,0fdh ;Prefix FD dw l20ach - db 0ffh,0edh,0 ;Prefix ED + db 0ffh,0edh ;Prefix ED dw l20b8h -t_op_branch0: - db 0ffh,0cdh,0 ;call mn + + db 0ffh,0cdh ;call mn dw l2080h - db 0ffh,0c3h,0 ;jp mn + db 0ffh,0c3h ;jp mn dw l208bh - db 0ffh,0e9h,0 ;jp () + db 0ffh,0e9h ;jp () dw l20a2h - db 0ffh,0c9h,0 ;ret + db 0ffh,0c9h ;ret dw l20dch - db 0ffh,0cfh,0 ;rst 8 + db 0ffh,0cfh ;rst 8 dw l2115h - db 0c7h,0c7h,0 ;rst n + db 0c7h,0c7h ;rst n dw l20f9h - db 0c7h,0c4h,0 ;call cc,mn + db 0c7h,0c4h ;call cc,mn dw l2080h - db 0f7h,010h,0 ;djnz d; jr d + db 0f7h,010h ;djnz d; jr d dw l2093h - db 0e7h,020h,0 ;jr cc,d + db 0e7h,020h ;jr cc,d dw l2093h - db 0c7h,0c2h,0 ;jp cc,mn + db 0c7h,0c2h ;jp cc,mn dw l208bh - db 0c7h,0c0h,0 ;ret cc + db 0c7h,0c0h ;ret cc dw l20c5h db 0 @@ -3760,91 +3973,6 @@ bp_tab: endm endm -expr_buf: -current_cseg defl $ - current_cseg - .phase current_phase + current_cseg - -start: - LD SP,ldr_end+(stack-ddtz_base) - LD DE,signon ;ldr_end+(expr_buf-ddtz_base) - LD C,BDOS_PSTR - CALL BDOS - - xor a - dec a - jp po,reloc - ld de,msgz80 - LD C,BDOS_PSTR - CALL BDOS - jp 0 - -reloc: - LD HL,ldr_end+ddtz_size ;start of reloc bitmap - ld bc,0108h ;init bit counter - - EXX - LD HL,(BDOS+1) - LD (ldr_end+(ddtz_bdos+1-ddtz_base)),HL - LD BC,ddtz_size-1 - LD D,B - LD E,0FFH - INC DE ;size rounded up to next page boundary - INC BC ;ddtz_size - OR A - SBC HL,DE ;BDOS - size - LD (BDOS+1),HL ;-> new BDOS entry - - push hl - PUSH BC - ld de,ldr_end - sbc hl,de - EX DE,HL ;-> DE - LD HL,ldr_size - add hl,bc - ld b,h - ld c,l - LD HL,TPA -reloc_lp: - EXX - djnz reloc_nl - ld b,c ;reload bit counter - LD e,(HL) ;get next 8 relocation bits - INC HL -reloc_nl: - sla e - EXX - JR NC,reloc_next - DEC HL - LD A,(HL) - ADD A,E - LD (HL),A - INC HL - LD A,(HL) - ADC A,D - LD (HL),A -reloc_next: - cpi - jp pe,reloc_lp - dec hl - - POP BC - pop de - EX DE,HL - ADD HL,BC - EX DE,HL - DEC DE - LDDR - LD HL,conbuf+2-ddtz_base - ADD HL,DE - JP (HL) - -current_phase defl $ - .dephase -current_cseg defl $ - - ds EXPR_BUF_SIZE - ($ - expr_buf) -expr_bufe: - ;------------------------------------------------------------------------------- last_S: @@ -3872,10 +4000,52 @@ last_L: dw TPA pbl_loop_adr: - dw 0 + dw 0addeh + +;------------------------------------------------------------------------------- + +conbuf:: + ds CONBUF_SIZE+1 + +;------------------------------------------------------------------------------- + + rept (STACK_SIZE+3)/4 + db 0deh,0adh,0beh,0efh + endm +stack:: +reg.l2: db 000h +reg.h2: db 000h +reg.e2: db 000h +reg.d2: db 000h +reg.c2: db 000h +reg.b2: db 000h +reg.f2: db 000h +reg.a2: db 000h + db 000h +reg.i: db 000h +reg.iy: dw 0000h +reg.ix: dw 0000h +reg.f: db 000h +reg.a: db 000h +reg.c: db 000h +reg.b: db 000h +reg.e: db 000h +reg.d: db 000h +reg.l: db 000h +reg.h: db 000h +reg_sp: dw TPA +reg.iff: + db 0f3h + db 0c3h +reg.pc: dw TPA + +cmd_rpt:dw mainloop + +;------------------------------------------------------------------------------- ddtz_size equ $-ddtz_base -ddtz_end: +prog_size equ $-start +ddtz_end:: ;-------------------------------------------------------------------------------