X-Git-Url: http://cloudbase.mooo.com/gitweb/ddt180.git/blobdiff_plain/b5b85b4cb3bbddbeb2726bad4666b7d012bf61f2..efc2486ea0340c32c372f5565a48eea068687cac:/ddt180.z80 diff --git a/ddt180.z80 b/ddt180.z80 index 235e469..81b68b4 100644 --- a/ddt180.z80 +++ b/ddt180.z80 @@ -6,22 +6,140 @@ ; - 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. +TPA equ 0100h + + cseg +ldr_start: + LD SP,stack + +; LD DE,signon +; LD C,BDOS_PSTR +; CALL BDOS + + ld hl,(1) ;wboot addr + ld de,?const + ld b,3 +vini_l: + inc hl + inc hl + inc hl + ex de,hl + inc hl + ld (hl),e + inc hl + ld (hl),d + inc hl + ex de,hl + djnz vini_l + +signon: + call pstr_inl + db 'DDTZ/180' + db ' - Version ' + maclib version.inc + defvers + dc CR,LF + +; 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 + + jp mainloop + ;------------------------------------------------------------------------------- ; Relocation loader ; -TPA equ 0100h - cseg - .phase TPA + LD HL,ddtz_end ;start of reloc bitmap + ld bc,0108h ;init bit counter - jp start - ds 3 + EXX + LD HL,(BDOS+1) + LD (ddtz_base+1),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 -ldr_end: -ldr_size equ $ - TPA -current_phase defl $ + 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: + inc hl + dec bc + ld a,b + or c + jr nz,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) - .dephase -current_cseg defl $ +ldr_end: +ldr_size equ $ - ldr_start ;------------------------------------------------------------------------------- ; DDT/Z core @@ -49,38 +167,20 @@ BDOS_PSTR equ 9 ;Print String 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 6 ;Size of a breakpoint record +BP_SIZE equ 4 ;Size of a breakpoint record ;------------------------------------------------------------------------------- ddtz_base: - jp ddtz_bdos + jp 0 l0003h: rst 30h di_or_ei: 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,'$' - -current_phase defl $ - .dephase -current_cseg defl $ - ds STACK_SIZE - (current_phase - signon) + ds STACK_SIZE stack: reg.l2: db 000h @@ -91,7 +191,7 @@ reg.c2: db 000h reg.b2: db 000h reg.f2: db 000h reg.a2: db 000h -l004eh: db 000h + db 000h reg.i: db 000h reg.iy: dw 0000h reg.ix: dw 0000h @@ -108,7 +208,6 @@ reg.iff: db 0f3h db 0c3h reg.pc: dw TPA -var.$: dw 0000h cmd_rpt:dw mainloop @@ -117,45 +216,13 @@ cmd_rpt:dw mainloop 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 - jr mainloop - ds CONBUF_SIZE + 3 - ($ - conbuf) ;------------------------------------------------------------------------------- -?const: -?conin: -?cono: - ret +?const: jp 0 ; return console input status +?conin: jp 0 ; return console input character +?cono: jp 0 ; send console output character CMDTAB: dw ERROR ;cmd_@ ;examine/substitute the displacement register @ @@ -187,14 +254,12 @@ CMDTAB: dw cmd_Z ;Zap (fill) memory with a byte string ERROR: -p_msg_error: call pstr_inl dc '?',CR,LF ;fall thru mainloop: ld sp,stack ld hl,(reg.pc) - ld (var.$),hl call bp_clr_temporary ld hl,(cmd_rpt) ld de,mainloop @@ -215,14 +280,14 @@ mainloop: jr c,ERROR cp 'Z'+1-'@' jr nc,ERROR - add a,a ld hl,CMDTAB - call add_hl_a + call add_hl_a2 ld a,(hl) inc hl ld h,(hl) ld l,a exe_hl: +CALL_HL: jp (hl) ;------------------------------------------------------------------------------- @@ -322,7 +387,8 @@ out.ascii: cp ' ' push af call nc,outbl - call outquote + call pstr_inl + dc '''' pop af jr nc,l0242h sub 0c0h @@ -334,7 +400,8 @@ l0242h: call outchar cp '''' call z,outchar - call outquote + call pstr_inl + dc '''' sla c pop bc ret nc @@ -349,10 +416,6 @@ outbl2: call outbl outbl: ld a,' ' - jr outchar - -outquote: - ld a,'''' outchar: push ix push iy @@ -373,21 +436,6 @@ outchar: pop ix ret -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 @@ -528,8 +576,6 @@ skipbl: call get_char_upper cp ' ' jr z,skipbl0 - cp TAB - jr z,skipbl0 or a ret @@ -565,6 +611,8 @@ chk_stack: ;------------------------------------------------------------------------------- +add_hl_a2: + add a,a add_hl_a: add a,l ld l,a @@ -577,6 +625,7 @@ cp_hl_de: sbc hl,de add hl,de ret + ;------------------------------------------------------------------------------- lookupch: @@ -630,22 +679,23 @@ l031eh: pop bc ret l0336h: - call sub_0345h + call str_sel_next l0339h: pop de and a pop bc ret -sel_dc_string: +str_sel: inc b -l033eh: - dec b - ret z - call sub_0345h - jr l033eh + jr str_sel2 +str_sel1: + call str_sel_next +str_sel2: + djnz str_sel1 + ret -sub_0345h: +str_sel_next: ld a,(hl) and a ret z @@ -758,91 +808,6 @@ l03b8h: expr: call skipbl expr1: - call do_subexpr - ret c - call do_rel_op - ret nc - push bc - push hl - call do_subexpr - jr c,error0 - ex de,hl - ex (sp),hl - and a - sbc hl,de - ld hl,0ffffh - pop de - ret - -;------------------------------------------------------------------------------- - -do_op_eq: - jr z,l03edh - jr l03ech -do_op_ne: - jr nz,l03edh - jr l03ech -do_op_le: - jr z,l03edh -do_op_lt: - jr c,l03edh - jr l03ech -do_op_gt: - jr z,l03ech -do_op_ge: - jr nc,l03edh -l03ech: - inc hl -l03edh: - and a - ret -do_rel_op: - push hl - ld hl,tab_eq_le_ge - call lookupch - jr nc,l041dh - ld a,b - or a - jr z,l0411h - ld a,(de) - cp '=' - jr nz,l0406h - inc de - inc b - inc b - jr l0411h -l0406h: - bit 0,b - jr z,l0411h - cp '>' - jr nz,l0411h - inc de - ld b,005h -l0411h: - ld hl,tab_func_eqlege - ld a,b - add a,a - call add_hl_a - ld c,(hl) - inc hl - ld b,(hl) - scf -l041dh: - pop hl - ret - -tab_eq_le_ge: - db '=<>',0 - -tab_func_eqlege: - dw do_op_eq - dw do_op_lt - dw do_op_gt - dw do_op_le - dw do_op_ge - dw do_op_ne - -do_subexpr: call do_factor ret c l0433h: @@ -976,8 +941,7 @@ do_binary_op: call lookupch ld a,b ld hl,tblf_opa - add a,a - call add_hl_a + call add_hl_a2 ld c,(hl) inc hl ld b,(hl) @@ -1010,7 +974,7 @@ do_factor: call get.number ret nc inc de - ld hl,(BDOS+1) + ld hl,ddtz_base-1 cp 'T' ret z ld hl,(high_load) @@ -1022,12 +986,6 @@ do_factor: ld hl,TPA cp 'L' ret z - ld hl,(var.$) - cp '$' - ret z - ld hl,ddtz_base - cp 'Z' - ret z cp '-' jr z,fact_factneg cp '~' @@ -1259,8 +1217,7 @@ l063eh: ld iy,(reg.pc) call p_disas_instr pop de - ex (sp),hl - push af + pop hl call crlf call p_f2 call outbl2 @@ -1268,8 +1225,6 @@ l063eh: l065bh: call p_regs djnz l065bh - pop af - pop hl jp crlf p_f: @@ -1277,13 +1232,13 @@ p_f: call p_flags ld a,(reg.iff) cp 0f3h - jp z,outbl + jr z,outbl_1 ld a,'E' jp outchar p_f2: ld a,(reg.f2) call p_flags - jp outbl + jr outbl_1 p_flags: push hl @@ -1332,10 +1287,10 @@ l06deh: ld a,(de) call out_hex l06e2h: - call outbl pop de pop hl - ret +outbl_1: + jp outbl b_06e9_start: DC 'A ' @@ -1443,11 +1398,10 @@ bp_clr_temporary: ; set breakpoints ; > BX ; clear all breakpoints -; > BX address [address..] +; > BX breakp [breakp..] ; clear breakpoints ; -; where breakp is: -; expression +; breakp can be any valid expression cmd_B: call skipbl @@ -1531,9 +1485,6 @@ bp_enter: pop de ld (ix+002h),l ld (ix+003h),h - call bp_get_count - ld (ix+004h),l - ld (ix+005h),h call next_arg pop af ld (ix+000h),a @@ -1551,15 +1502,6 @@ bp_get_freeslot: error12 jp ERROR -bp_get_count: - call skipbl - ld hl,1 - cp ':' - ret nz - inc de - call expr - jr c,error12 - ret ;------------------------------------------------------------------------------- ; Breakpoint handling routine. @@ -1627,32 +1569,14 @@ sub_0913h: ld d,(ix+003h) ld hl,(reg.pc) call cp_hl_de - push bc - call z,sub_0942h - pop bc -l0938h: - - call bpl_next - ex af,af' - ret - -sub_0942h: + jr nz,l0938h ex af,af' res 7,a - ex af,af' - ld e,(ix+004h) - ld d,(ix+005h) - dec de - ld a,d - or e - jr z,l0974h - ld (ix+004h),e - ld (ix+005h),d - ret -l0974h: - ex af,af' or (ix+000h) ex af,af' +l0938h: + call bpl_next + ex af,af' ret bp_restore_mem: @@ -1693,8 +1617,6 @@ bp_tst_e: bp_trace_enter: call bp_get_freeslot - ld (ix+004h),001h - ld (ix+005h),000h ld (ix+002h),l ld (ix+003h),h ld a,(b_21e2_start) @@ -1789,15 +1711,13 @@ cmd_X: jp nc,p_cpustat0 call assert_eol ld a,b - cp 01eh + cp 25 jr z,l0c5fh - cp 01fh + cp 26 jr z,l0c4fh - cp 01dh - jp z,ERROR ex de,hl ld hl,t_reg_names - call sel_dc_string + call pstr_sel call l0c33h call outbl @@ -1822,7 +1742,6 @@ l0c30h: ret l0c33h: - call pstr call pstr_inl dc '=' ld a,(de) @@ -1907,38 +1826,33 @@ sub_0caeh: ret t_reg_names: - DC 'BC''' - DC 'DE''' - DC 'HL''' - DC 'BC' - DC 'DE' - DC 'HL' - DC 'A''' - DC 'B''' - DC 'C''' - DC 'D''' - DC 'E''' - DC 'H''' - DC 'L''' - DC 'A' - DC 'B' - DC 'C' - DC 'D' - DC 'E' - DC 'H' - DC 'L' - DC 'IX' - DC 'IY' - DC 'SP' - DC 'PC' - DC 'X' - DC 'Y' - DC 'S' - DC 'P' - DC 'I' - DC 'IP' - DC 'F''' - DC 'F' + DC 'BC''' ;0 + DC 'DE''' ;1 + DC 'HL''' ;2 + DC 'BC' ;3 + DC 'DE' ;4 + DC 'HL' ;5 + DC 'A''' ;6 + DC 'B''' ;7 + DC 'C''' ;8 + DC 'D''' ;9 + DC 'E''' ;10 + DC 'H''' ;11 + DC 'L''' ;12 + DC 'A' ;13 + DC 'B' ;14 + DC 'C' ;15 + DC 'D' ;16 + DC 'E' ;17 + DC 'H' ;18 + DC 'L' ;19 + DC 'IX' ;20 + DC 'IY' ;21 + DC 'SP' ;22 + DC 'PC' ;23 + DC 'I' ;24 + DC 'F''' ;25 + DC 'F' ;26 DB 0 b_0cfa_start: @@ -1990,18 +1904,8 @@ b_0cfa_start: dw reg_sp db 003h dw reg.pc - db 003h - dw reg.ix - db 003h - dw reg.iy - db 003h - dw reg_sp - db 003h - dw reg.pc db 000h dw reg.i - db 003h - dw l004eh db 000h dw reg.f2 db 000h @@ -2120,29 +2024,17 @@ l0dedh: call crlf l0e10h: pop bc - inc hl inc de - dec bc - ld a,b - or c - jr nz,l0dedh + cpi + jp pe,l0dedh ret ;------------------------------------------------------------------------------- -; > M[V] startaddr endaddr destaddr -; Move memory [and verify] +; > M startaddr endaddr destaddr +; Move memory cmd_M: - call get_char_upper - cp 'V' - jr nz,l0e1fh - inc de -l0e1fh: - push af call sub_034eh - push hl - push de - push bc call cp_hl_de jr nc,cmdm_up add hl,bc @@ -2155,11 +2047,6 @@ l0e1fh: db 01h ;swallow ldir instruction (ld bc,...) cmdm_up: ldir - pop bc - pop de - pop hl - pop af - jr z,l0dedh ret ;------------------------------------------------------------------------------- @@ -2192,32 +2079,31 @@ cmd_H: ; Query memory for a byte string [Justified] cmd_Q: - call get_char_upper - sub 'J' - ld (cmd_Q_jopt),a - jr nz,l0e8dh - inc de -l0e8dh: call get_arg_range push bc push hl call sub_0ee6h pop hl l0e96h: - call sub_0ed7h + push hl + push de + push bc +l0edah: + ld a,(de) + cp (hl) + jr nz,l0ee2h + inc de + inc hl + djnz l0edah +l0ee2h: + pop bc + pop de + pop hl jr nz,l0eb0h push bc - push hl - ld a,(cmd_Q_jopt) - or a - jr nz,l0ea7h - ld bc,-8 - add hl,bc -l0ea7h: ld bc,16 - and a + and a ;clear carry call sub_0f58h - pop hl pop bc l0eb0h: inc hl @@ -2256,23 +2142,6 @@ l0ed3h: pop hl ret -sub_0ed7h: - push hl - push de - push bc -l0edah: - ld a,(de) - cp (hl) - jr nz,l0ee2h - inc de - inc hl - djnz l0edah -l0ee2h: - pop bc - pop de - pop hl - ret - sub_0ee6h: ld hl,conbuf+1 call sub_0ef7h @@ -2283,26 +2152,13 @@ sub_0ee6h: ret nz jp ERROR -sub_0ef7h: - db 0e6h ; and 037h (clear carry) -sub_0ef8h: +sub_0ef7h: ;from cmd_Q, cmd_Z + db 0e6h ;and 037h (clear carry) +sub_0ef8h: ;from cmd_S scf l0ef9h: push af call next_arg - cp 'W' - jr nz,l0f0eh - inc de - push hl - call sub_035dh - ex de,hl - ex (sp),hl - ld (hl),e - inc hl - ld a,d - pop de - jr l0f1ah -l0f0eh: cp '''' jr z,l0f1eh push hl @@ -2310,7 +2166,6 @@ l0f0eh: ld a,l pop hl jr c,l0f42h -l0f1ah: ld (hl),a inc hl jr l0f3ah @@ -2364,8 +2219,7 @@ sub_0f58h: push af l0f5ch: call out_hl - call z,outbl2 - call outbl + call outbl2 ld de,0 l0f68h: ld a,(hl) @@ -2463,8 +2317,9 @@ l16c6h: call i.gethexbyte ;checksum ld a,c and a - jp nz,ERROR ;exit if checksum error + jr nz,error2 ;exit if checksum error jr w_recstart ;next record + rdhex_done: pop hl call i.gethexbyte @@ -2537,7 +2392,7 @@ p_max_high: call out_hl call pstr_inl DC ' Top = ' - ld hl,(BDOS+1) + ld hl,ddtz_base-1 call out_hl jp crlf @@ -2553,24 +2408,6 @@ p_max_high: ;cmd_A: - -CALL_HL: - jp (hl) - -;------------------------------------------------------------------------------- - - - - -b_176d_start: - DC 'AF,AF''' -l1773h: - DC 'DE,HL' - DC '(SP),HL' - DC '(SP),IX' - DC '(SP),IY' - db 0 - ;------------------------------------------------------------------------------- ; >>L [startaddr] [endaddr] ; List disassembled code @@ -2611,52 +2448,34 @@ l190fh: cmdl_p_line: push hl - call p_disas_line - call crlf - pop hl - ld c,b - ld b,0 - add hl,bc - ld (last_L),hl - ret - -p_disas_line: - call outbl2 call out_hl - call z,outbl - call outbl + call outbl2 sub a ld (con_col),a push hl pop iy call p_disas_instr - ret z - - ld c,15 - call p_goto_col - ; fall thru -;------------------------------------------------------------------------------- + call crlf + pop hl + ld c,b + ld b,0 + add hl,bc + ld (last_L),hl ret ;------------------------------------------------------------------------------- p_disas_instr: - sub a - ld (disas_argtype),a call disas_get_instrlen jr nc,l197fh push bc ld a,(con_col) add a,5 ld c,a - call pstr + call pstr ;print mnemonic call p_goto_col - ex de,hl - call call_hl + call pr_instr_args ;print arguments pop bc - ld a,(disas_argtype) - ld hl,(disas_arg_16) - or a scf ret @@ -2672,7 +2491,7 @@ disas_get_instrlen: ld (isprefix_ixiy),a ld a,(iy+000h) cp 0edh - jp z,disas_pfx.ED + jr z,disas_pfx.ED cp 0ddh jr z,l19abh cp 0fdh @@ -2680,8 +2499,8 @@ disas_get_instrlen: sub_19a0h: ld a,(iy+000h) cp 0cbh - jp z,disas_pfx.CB - jp disas_nopfx + jr z,disas_pfx.CB + jr disas_nopfx l19abh: ld a,1 jr l19b1h @@ -2701,6 +2520,81 @@ l19b1h: ;------------------------------------------------------------------------------- +disas_nopfx: + ld hl,b_1b54_start ;2 byte opcodes + call lookup_op_arg + ld b,2 + ret c + ld hl,b_1ab6_start ;1 byte opcodes (no parameters) + call lookup_op + ld b,1 + ret c + ld hl,b_1ad1_start ;1 byte opcodes + call lookup_op_arg + ld b,1 + ret c + ld hl,b_1b9b_start ;3 byte opcodes + call lookup_op_arg + ld b,3 + ret + +;------------------------------------------------------------------------------- + +disas_pfx.ED: + inc iy + ld hl,l228bh + call lookup_op_arg + ld b,3 + ret c + 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 + +;------------------------------------------------------------------------------- + +disas_pfx.CB: + push iy + inc iy + ld a,(isprefix_ixiy) + and a + jr z,l1a42h + inc iy +l1a42h: + ld hl,b_1c55_start + call lookup_op_arg + pop iy + ld b,2 + ret + +;------------------------------------------------------------------------------- + disas_pfx.DDFD: inc iy ld hl,b_19ef_start @@ -2777,117 +2671,74 @@ l1a0ah: ;------------------------------------------------------------------------------- -disas_pfx.ED: - inc iy - ld hl,b_1bc9_start - call sub_1a72h - ld b,2 - ret c - ld hl,b_1bf4_start - call lookup_opc - ld b,2 - ret c - - ld hl,l228bh - call lookup_opc - ld b,3 - ret c - ld hl,b_1c40_start - call lookup_opc - ld b,4 - ret - -;------------------------------------------------------------------------------- - -disas_pfx.CB: - push iy - inc iy - ld a,(isprefix_ixiy) +test_DDFD: + ld a,(hl) and a - jr z,l1a42h - inc iy -l1a42h: - ld hl,b_1c55_start - call lookup_opc - pop iy - ld b,2 - ret - -;------------------------------------------------------------------------------- - -disas_nopfx: - ld hl,b_1b54_start - call lookup_opc - ld b,2 - ret c - ld hl,b_1ab6_start - call sub_1a72h - ld b,1 - ret c - ld hl,b_1ad1_start - call lookup_opc - ld b,1 - ret c - ld hl,b_1b9b_start - call lookup_opc - ret nc - ld b,3 + ret z + inc hl + cp (iy+000h) + jr nz,test_DDFD + scf ret -;------------------------------------------------------------------------------- - -sub_1a72h: +lookup_op: ld a,(hl) + inc hl cp 0ffh ret z cp (iy+000h) jr z,l1a7fh inc hl - inc hl - jr sub_1a72h + jr lookup_op l1a7fh: - ld de,l1c97h - 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_opc: - 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_opc - ret + jr lookup_branch_op -l1aa8h: - inc hl - ld c,(hl) - 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 @@ -2895,343 +2746,446 @@ get_mnemonic: ; 1 byte opcodes (no parameters) ; Format: db opcode, t_MNEMONICS-index b_1ab6_start: - db 076h,039h ;halt - db 0d9h,036h ;exx - db 0f3h,02ch ;di - db 0fbh,032h ;ei - db 000h,069h ;nop - db 007h,09eh ;rlca - db 00fh,0adh ;rrca - db 017h,098h ;rla - db 01fh,0a7h ;rra - db 027h,026h ;daa - db 02fh,023h ;cpl - db 037h,0bah ;scf - db 03fh,010h ;ccf + 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 ; 1 byte opcodes ; Format: db mask, match, t_MNEMONICS-index -; dw argument formating fuction +; dw argument formating function b_1ad1_start: - db 0c0h,040h,056h ;ld r,r - dw p_arg_r_r - db 0f8h,080h,003h ;add a,r - dw p_arg_a_r - db 0f8h,088h,000h ;adc a,r - dw p_arg_a_r - db 0f8h,090h,0c9h ;sub r - dw p_arg_rs - db 0f8h,098h,0b7h ;sbc a,r - dw p_arg_a_r - db 0f8h,0a0h,006h ;and r - dw p_arg_rs - db 0f8h,0a8h,0cch ;xor r - dw p_arg_rs - db 0f8h,0b0h,06ch ;or r - dw p_arg_rs - db 0f8h,0b8h,013h ;cp r - dw p_arg_rs - db 0c7h,0c0h,08bh ;ret cc - dw p_arg_cc - db 0c7h,0c7h,0b4h ;rst - dw l1c98h - db 0ffh,0c9h,08bh ;ret - dw l1c97h - db 0cfh,0c1h,081h ;pop rr - dw p_arg_zz - db 0cfh,0c5h,084h ;push rr - dw p_arg_zz - db 0ffh,0e3h,034h ;ex (sp),hl - dw l1ca0h - db 0ffh,0e9h,052h ;jp (hl) - dw l1caeh - db 0ffh,0ebh,034h ;ex de,hl - dw p_arg_ex_dehl - db 0ffh,0f9h,056h ;ld sp,hl - dw l1cc1h - db 0cfh,003h,041h ;inc rr - dw p_arg_ww - db 0cfh,00bh,029h ;dec rr - dw p_arg_ww - db 0c7h,004h,041h ;inc r - dw p_arg_r - db 0c7h,005h,029h ;dec r - dw p_arg_r - db 0ffh,008h,034h ;ex af,af' - dw p_arg_ex_afaf - db 0cfh,009h,003h ;add hl,rr - dw l1cd3h - db 0efh,002h,056h ;ld (rr),a ;rr=bc,de - dw l1cdch - db 0efh,00ah,056h ;ld a,(rr) ;rr=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,056h ;ld r,nn - dw l1cfah - db 0ffh,0c6h,003h ;add a,nn - dw l1cf5h - db 0ffh,0ceh,000h ;adc a,nn - dw l1cf5h - db 0ffh,0d6h,0c9h ;sub a,nn - dw l1d09h - db 0ffh,0deh,0b7h ;sbc a,nn - dw l1cf5h - db 0ffh,0e6h,006h ;and a,nn - dw l1d09h - db 0ffh,0eeh,0cch ;xor nn - dw l1d09h - db 0ffh,0f6h,06ch ;or nn - dw l1d09h - db 0ffh,0feh,013h ;cp a,nn - dw l1d09h - db 0ffh,010h,02eh ;djnz - dw p_arg_jrel - db 0ffh,018h,054h ;jr - dw p_arg_jrel - db 0e7h,020h,054h ;jr cc, - dw p_arg_cc_jrel - db 0ffh,0d3h,076h ;out (nn),a - dw l1d37h - db 0ffh,0dbh,03fh ;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,052h ;jp cc,mn - dw p_arg_cc_mn - db 0c7h,0c4h,00ch ;call cc,mn - dw p_arg_cc_mn - db 0cfh,001h,056h ;ld ww,mn - dw p_arg_ww_mn - db 0ffh,0c3h,052h ;jp mn - dw p_arg_mn - db 0ffh,0cdh,00ch ;call mn - dw p_arg_mn - db 0ffh,022h,056h ;ld (mn),hl - dw p_arg_addr_hl - db 0ffh,02ah,056h ;ld hl,(mn) - dw p_arg_hl_addr - db 0ffh,032h,056h ;ld (mn),a - dw p_arg_addr_a - db 0ffh,03ah,056h ;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,066h ;neg - db 045h,092h ;retn - db 04dh,08eh ;reti - db 067h,0b1h ;rrd - db 06fh,0a2h ;rld - db 0a0h,05fh ;ldi - db 0a1h,01ch ;cpi - db 0a2h,04bh ;ini - db 0a3h,07dh ;outi - db 0a8h,058h ;ldd - db 0a9h,015h ;cpd - db 0aah,044h ;ind - db 0abh,079h ;outd - db 0b0h,062h ;ldir - db 0b1h,01fh ;cpir - db 0b2h,04eh ;inir - db 0b3h,072h ;otir - db 0b8h,05bh ;lddr - db 0b9h,018h ;cpdr - db 0bah,047h ;indr - db 0bbh,06eh ;otdr - db 08bh,0d5h ;otdm - db 09bh,0d9h ;otdmr - db 083h,0deh ;otim - db 093h,0e2h ;otimr - db 076h,0ebh ;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 0e7h,040h,03fh ;in r,(c) ;r=b,c,d,e - dw p_arg_in_c ; - db 0f7h,060h,03fh ;in r,(c) ;r=h,l - dw p_arg_in_c ; - db 0ffh,078h,03fh ;in r,(c) ;r=a - dw p_arg_in_c ; - db 0e7h,041h,076h ;out (c),r ;r=b,c,d,e - dw p_arg_out_c ; - db 0f7h,061h,076h ;out (c),r ;r=h,l - dw p_arg_out_c ; - db 0ffh,079h,076h ;out (c),r ;r=a - dw p_arg_out_c ; - db 0cfh,042h,0b7h ;sbc hl,rr - dw l1dcah ; - db 0cfh,04ah,000h ;adc hl,rr - dw l1dcah ; - db 0ffh,046h,03dh ;im 0 - dw l1d85h ; - db 0ffh,056h,03dh ;im 1 - dw l1d89h ; - db 0ffh,05eh,03dh ;im 2 - dw l1d8dh ; - db 0ffh,047h,056h ;ld i,a - dw l1d92h ; - db 0ffh,057h,056h ;ld a,i - dw l1d97h ; - db 0ffh,04fh,056h ;ld r,a - dw l1d9ch ; - db 0ffh,05fh,056h ;ld a,r - dw l1da1h - db 0cfh,04ch,0d2h ;mlt rr - dw p_arg_ww - db 0c7h,004h,0eeh ;tst r - dw p_arg_r + 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 ; + 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 0e7h,000h,0cfh ;in0 r,(m) ;r=b,c,d,e - dw p_arg_r_m - db 0f7h,020h,0cfh ;in0 r,(m) ;r=h,l - dw p_arg_r_m - db 0ffh,038h,0cfh ;in0 a,(m) - dw p_arg_r_m - db 0e7h,001h,0e7h ;out0 (m),r ;r=b,c,d,e - dw p_arg_m_r - db 0f7h,021h,0e7h ;out0 (m),r ;r=h,l - dw p_arg_m_r - db 0ffh,039h,0e7h ;out0 (m),a - dw p_arg_m_r - db 0ffh,064h,0eeh ;tst m - dw l1d09h - db 0ffh,074h,0f1h ;tstio m - dw l1d09h + 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 + 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 0efh,043h,056h ;ld (mn),ww ;ww=bc,de - dw p_arg_addr_ww - db 0ffh,073h,056h ;ld (mn),sp - dw p_arg_addr_ww - db 0efh,04bh,056h ;ld ww,(mn) ;ww=bc,de - dw p_arg_ww_addr - db 0ffh,07bh,056h ;ld sp,(mn) - 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,09bh ;rlc g - dw l1e03h - db 0f8h,008h,0aah ;rrc g - dw l1e03h - db 0f8h,010h,096h ;rl g - dw l1e03h - db 0f8h,018h,0a5h ;rr g - dw l1e03h - db 0f8h,020h,0c0h ;sla g - dw l1e03h - db 0f8h,028h,0c3h ;sra g - dw l1e03h - db 0f8h,038h,0c6h ;srl g - dw l1e03h - db 0c0h,040h,009h ;bit b,g - dw p_arg_bitop - db 0c0h,080h,088h ;res b,g - dw p_arg_bitop - db 0c0h,0c0h,0bdh ;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_r_r: - call p_arg_r - call p_char_comma - jp p_arg_rs -p_arg_a_r: - call p_A_comma - jp p_arg_rs -l1c97h: - ret -p_arg_r_m: - call p_arg_r - 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_arg_r +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 -l1c98h: - 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 + +; 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) + +; 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 + +; 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] + +; 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 -l1caeh: - call p_char_lparen - call p_arg_hlixiy - jr out_rparen -p_arg_ex_dehl: - ld hl,l1773h - jp pstr +;------------------------------------------------------------------------------- -l1cc1h: - call pstr_inl - DC 'SP,' - jp p_arg_hlixiy - -p_arg_ex_afaf: - ld hl,b_176d_start - jp pstr - -l1cd3h: - call p_arg_hlixiy - call p_char_comma - jp p_arg_ww -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_arg_ww - jr out_rparen - -l1cf5h: - call p_A_comma - jr l1d09h -l1cfah: - call p_arg_r - call p_char_comma +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 @@ -3242,194 +3196,59 @@ p_arg_jrel: add hl,bc inc hl inc hl - jr l1d4eh - -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 + jr out_hl_0 -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: - ld a,002h -sub_1d50h: - ld (disas_argtype),a - ld (disas_arg_16),hl +out_hl_0: jp out_hl -p_arg_ww_mn: - call p_arg_ww - 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 - -l1d92h: - ld hl,b_1da7_start - jr l1da4h -l1d97h: - ld hl,l1daah - jr l1da4h -l1d9ch: - ld hl,l1dadh - jr l1da4h -l1da1h: - ld hl,l1db0h -l1da4h: - jp pstr - -b_1da7_start: - DC 'I,A' -l1daah: - DC 'A,I' -l1dadh: - DC 'R,A' -l1db0h: - DC 'A,R' - -p_arg_in_c: - call p_arg_r - call p_char_comma - ld hl,t__C_ - jp pstr +p_ir: + rra + rra + rra + and 03 + ld hl,t_arg_IR + jr p_arg -p_arg_out_c: - ld hl,t__C_ - call pstr - call p_char_comma - jr p_arg_r - -l1dcah: - call p_arg_hlixiy - call p_char_comma - jp p_arg_ww - -p_arg_addr_ww: - call p_arg_addr - call p_char_comma - jp p_arg_ww - -p_arg_ww_addr: - call p_arg_ww - call p_char_comma - jr p_arg_addr - -p_arg_a_addr: - call p_A_comma -p_arg_addr: - call p_char_lparen - ld l,(iy+001h) - ld h,(iy+002h) - ld a,001h - call sub_1d50h - jr p_char_rparen -p_arg_bitop: +get_cb_opc: ld a,(isprefix_ixiy) and a - jr nz,l1defh ld a,(iy+001h) - jr l1df2h -l1defh: + ret z ld a,(iy+002h) -l1df2h: - push af + ret + +p_y: + call get_cb_opc rra rra rra and 007h - add a,'0' - call outchar - call p_char_comma - pop af - jr p_arg_r0 + jp out_dgt -l1e03h: - ld a,(isprefix_ixiy) - and a - jr nz,l1e0eh - ld a,(iy+001h) - jr l1e11h -l1e0eh: - ld a,(iy+002h) -l1e11h: - jr p_arg_r0 +p_rz_cb: + call get_cb_opc + jr p_rz -p_arg_r: - ld a,(iy+000h) +p_ry: rra rra rra - jr p_arg_r0 -p_arg_rs: - ld a,(iy+000h) -p_arg_r0: +p_rz: and 007h cp 006h - jr nz,p_arg_r1 + ld b,a + ld hl,t_arg_r + jr nz,p_arg0 ld a,(isprefix_ixiy) and a - ld a,006h - jr z,p_arg_r1 - ld hl,b_1e78_start - ld a,(isprefix_ixiy) + jr z,p_arg0 + ld hl,t_lp_IXIY dec a - jr z,l1e4dh - ld hl,l1e7bh -l1e4dh: - call pstr + call p_arg ld a,(iy+001h) push af rlca @@ -3442,133 +3261,165 @@ l1e4dh: l1e61h: call outchar pop af - jp p_arg_nn_rp - -p_arg_r1: - ld hl,t_BCDEHL_HL_A - jr p_arg - -b_1e78_start: - DC '(IX' -l1e7bh: - DC '(IY' + call out_hex + ld a,')' + jp outchar -p_arg_hlixiy: - ld a,(isprefix_ixiy) - ld hl,t_HL.IX.IY - jr p_arg -p_arg_zz: - ld hl,t_BC.DE.HL.AF - jr l1e8eh -p_arg_ww: - ld hl,t_BC.DE.HL.SP -l1e8eh: - ld a,(iy+000h) +p_rp2: + ld hl,t_arg_rp2 + db 0ddh ;swallow t_arg_rp in ix +p_rp: + ld hl,t_arg_rp 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_arg_cc: - ld a,(iy+000h) -p_arg_cc0: +p_ccy2: + and 018h +p_ccy: rra rra rra and 007h - ld hl,t_tstfl_ZCPS + ld hl,t_arg_cc p_arg: ld b,a - call sel_dc_string - jp pstr +p_arg0: + ;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 + +pstr_inl: + ex (sp),hl + call pstr + ex (sp),hl + ret ;------------------------------------------------------------------------------- +opc macro x + +i_&x equ opc_index +;o_&x equ $-opc_tabstart + dc '&x' +opc_index defl opc_index+1 + endm + t_MNEMONICS: - DC 'ADC' - DC 'ADD' - DC 'AND' - DC 'BIT' - DC 'CALL' - DC 'CCF' - DC 'CP' - DC 'CPD' - DC 'CPDR' - DC 'CPI' - DC 'CPIR' - DC 'CPL' - DC 'DAA' - DC 'DEC' - DC 'DI' - DC 'DJNZ' - DC 'EI' - DC 'EX' - DC 'EXX' - DC 'HALT' - DC 'IM' - DC 'IN' - DC 'INC' - DC 'IND' - DC 'INDR' - DC 'INI' - DC 'INIR' - DC 'JP' - DC 'JR' - DC 'LD' - DC 'LDD' - DC 'LDDR' - DC 'LDI' - DC 'LDIR' - DC 'NEG' - DC 'NOP' - DC 'OR' - DC 'OTDR' - DC 'OTIR' - DC 'OUT' - DC 'OUTD' - DC 'OUTI' - DC 'POP' - DC 'PUSH' - DC 'RES' - DC 'RET' - DC 'RETI' - DC 'RETN' - DC 'RL' - DC 'RLA' - DC 'RLC' - DC 'RLCA' - DC 'RLD' - DC 'RR' - DC 'RRA' - DC 'RRC' - DC 'RRCA' - DC 'RRD' - DC 'RST' - DC 'SBC' - DC 'SCF' - DC 'SET' - DC 'SLA' - DC 'SRA' - DC 'SRL' - DC 'SUB' - DC 'XOR' - DC 'IN0' - DC 'MLT' - DC 'OTDM' - DC 'OTDMR' - DC 'OTIM' - DC 'OTIMR' - DC 'OUT0' - DC 'SLP' - DC 'TST' - DC 'TSTIO' +;opc_tabstart defl $ +opc_index defl 0 +; 1-byte other + opc NOP + opc LD + opc INC + opc DEC + opc DJNZ + opc JR + opc HALT + + opc RLCA + opc RRCA + opc RLA + opc RRA + opc DAA + opc CPL + opc SCF + opc CCF + +; 1-byte "alu" + opc ADD + opc ADC + opc SUB + opc SBC + opc AND + opc XOR + opc OR + opc CP + + opc RET + opc POP + opc JP + opc CALL + opc PUSH + opc RST + opc OUT + opc EXX + opc IN + opc EX + opc DI + opc EI +; CB + opc RLC + opc RRC + opc RL + opc RR + opc SLA + opc SRA + opc SLL + opc SRL + opc BIT + opc RES + opc SET + +; ED + opc NEG + opc RETN + opc RETI + opc IM + opc RRD + opc RLD + +; Block instructions + opc LDI + opc CPI + opc INI + opc OUTI + opc LDD + opc CPD + opc IND + opc OUTD + opc LDIR + opc CPIR + opc INIR + opc OTIR + opc LDDR + opc CPDR + opc INDR + opc OTDR + +; Z180 + opc IN0 + opc OUT0 + opc TST + opc MLT + opc TSTIO + opc SLP + opc OTIM + opc OTDM + opc OTIMR + opc OTDMR + DB 0 -t_BCDEHL_HL_A: +t_arg_r: DC 'B' DC 'C' DC 'D' @@ -3578,26 +3429,24 @@ t_BCDEHL_HL_A: DC '(HL)' DC 'A' DB 0 -t_BC.DE.HL.SP: +t_arg_rp: DC 'BC' DC 'DE' DC 'HL' DC 'SP' DB 0 -t_BC.DE.HL.AF: +t_arg_rp2: DC 'BC' DC 'DE' - DC 'HL' DC 'AF' DB 0 t_HL.IX.IY: DC 'HL' - DC 'IX' DC 'IY' DB 0 -t_tstfl_ZCPS: +t_arg_cc: DC 'NZ' DC 'Z' DC 'NC' @@ -3606,17 +3455,20 @@ t_tstfl_ZCPS: DC 'PE' DC 'P' DC 'M' - DC 'NE' - DC 'EQ' - DC 'GE' - DC 'LT' - DC 'NV' - DC 'V' - DB 0 -t__C_: - DC '(C)' DB 0 +t_lp_IXIY: + DC '(IX' + DC '(IY' + +t_arg_IR: + DC 'I,A' + DC 'R,A' + DC 'A,I' + DC 'A,R' + db 0 + + ;------------------------------------------------------------------------------- tc_set_bp: @@ -3627,7 +3479,7 @@ tc_set_bp: ld de,BDOS and a sbc hl,de - ld hl,l20edh + ld hl,l20edh ;set break after BDOS call jr z,l2031h ld iy,(reg.pc) call disas_get_instrlen @@ -3638,8 +3490,8 @@ tc_set_bp: add hl,bc call bp_trace_enter ld iy,(reg.pc) - ld hl,b_2039_start - call lookup_opc + ld hl,t_op_branch + call lookup_branch_op ccf ret c ex de,hl @@ -3652,36 +3504,35 @@ l2037h: ;------------------------------------------------------------------------------- -b_2039_start: - db 0ffh,0ddh,000h ;Prefix DD +t_op_branch: + db 0ffh,0ddh ;Prefix DD dw l20a7h - db 0ffh,0fdh,000h ;Prefix FD + db 0ffh,0fdh ;Prefix FD dw l20ach - db 0ffh,0edh,000h ;Prefix ED + db 0ffh,0edh ;Prefix ED dw l20b8h -b_2048_start: - db 0ffh,0cdh,000h ;call mn + db 0ffh,0cdh ;call mn dw l2080h - db 0ffh,0c3h,000h ;jp mn + db 0ffh,0c3h ;jp mn dw l208bh - db 0ffh,0e9h,000h ;jp () + db 0ffh,0e9h ;jp () dw l20a2h - db 0ffh,0c9h,000h ;ret + db 0ffh,0c9h ;ret dw l20dch - db 0ffh,0cfh,000h ;rst 8 + db 0ffh,0cfh ;rst 8 dw l2115h - db 0c7h,0c7h,000h ;rst n + db 0c7h,0c7h ;rst n dw l20f9h - db 0c7h,0c4h,000h ;call cc,mn + db 0c7h,0c4h ;call cc,mn dw l2080h - db 0f7h,010h,000h ;djnz d; jr d + db 0f7h,010h ;djnz d; jr d dw l2093h - db 0e7h,020h,000h ;jr cc,d + db 0e7h,020h ;jr cc,d dw l2093h - db 0c7h,0c2h,000h ;jp cc,mn + db 0c7h,0c2h ;jp cc,mn dw l208bh - db 0c7h,0c0h,000h ;ret cc + db 0c7h,0c0h ;ret cc dw l20c5h db 0 @@ -3758,7 +3609,7 @@ l20d7h: l20dch: l20edh: - ld hl,(reg_sp) + ld hl,(reg_sp) ;break on return address ld e,(hl) inc hl ld d,(hl) @@ -3779,7 +3630,6 @@ l20f9h: ld a,(b_21e2_start) and a ret z - scf ret @@ -3844,91 +3694,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: @@ -3942,9 +3707,6 @@ last_O_addr: last_O_val: db 0 -cmd_Q_jopt: - db -1 - last_D: dw TPA @@ -3957,13 +3719,9 @@ isprefix_ixiy: db 0 last_L: dw TPA -disas_arg_16: - dw 0 -disas_argtype: - db 0 pbl_loop_adr: - dw 0 + dw 0addeh ddtz_size equ $-ddtz_base ddtz_end: