X-Git-Url: http://cloudbase.mooo.com/gitweb/z180-stamp.git/blobdiff_plain/fecee2418b6aea15008ed6d3a856d202d59a5cdb..c3ce66a888beadf2a6d524101dd009d5acd452ae:/z180/ddtz.180 diff --git a/z180/ddtz.180 b/z180/ddtz.180 index e5d48e1..d18330c 100644 --- a/z180/ddtz.180 +++ b/z180/ddtz.180 @@ -957,449 +957,455 @@ do_op_mod: ex de,hl jr l0b58h +; divide x/y +; hl: x +; de: y +; return: +; hl: q (x/y) +; de: r (x%y) + DIV_HL_DE: - push bc - ex de,hl - ld b,h - ld c,l - ld hl,0 - ld a,16 + push bc + ex de,hl ;de = x, hl = y + ld b,h ;bc = y + ld c,l + ld hl,0 ;r = 0 + ld a,16 ;count + +; de: x (x shifted out, q shifted in) +; bc: y +; hl: r (initially 0) + l0b89h: - push af - add hl,hl - ex de,hl - xor a - add hl,hl - ex de,hl - adc a,l - sub c - ld l,a - ld a,h - sbc a,b - ld h,a - inc de - jr nc,l0b9ah - add hl,bc - dec de -l0b9ah: - pop af - dec a - jr nz,l0b89h - ex de,hl - pop bc + ex de,hl ;x + add hl,hl ;x <<= 1 + ex de,hl ;r + adc hl,hl ;r <<= 1 + + or a + sbc hl,bc + inc de + jr nc,div_no_restore + add hl,bc + dec de +div_no_restore: + dec a + jr nz,l0b89h + ex de,hl ;hl: q de: r + pop bc ret do_op_and: - ld a,h - and d - ld h,a - ld a,l - and e - ld l,a - jr l0b58h + ld a,h + and d + ld h,a + ld a,l + and e + ld l,a + jr l0b58h do_op_or: - ld a,h - or d - ld h,a - ld a,l - or e - ld l,a - jr l0b58h + ld a,h + or d + ld h,a + ld a,l + or e + ld l,a + jr l0b58h do_op_xor: - ld a,h - xor d - ld h,a - ld a,l - xor e - ld l,a - jr l0b58h + ld a,h + xor d + ld h,a + ld a,l + xor e + ld l,a + jr l0b58h do_binary_op: - push hl - ld hl,tab_op_a - call lookupch - ld a,b - ld hl,tab_func_opa - add a,a - call ADD_HL_A - ld c,(hl) - inc hl - ld b,(hl) - pop hl + push hl + ld hl,tab_op_a + call lookupch + ld a,b + ld hl,tab_func_opa + add a,a + call ADD_HL_A + ld c,(hl) + inc hl + ld b,(hl) + pop hl ret tab_op_a: DB '+-*/%&!#',0 tab_func_opa: - defw do_op_add - defw do_op_sub - defw do_op_mlt - defw do_op_div - defw do_op_mod - defw do_op_and - defw do_op_or - defw do_op_xor - defw 0 + defw do_op_add + defw do_op_sub + defw do_op_mlt + defw do_op_div + defw do_op_mod + defw do_op_and + defw do_op_or + defw do_op_xor + defw 0 fact_factor: - call do_factor - ret nc - jp ERROR + call do_factor + ret nc + jp ERROR do_factor: - call chk.sp - call get.number - ret nc - inc de - ld hl,TOPRAM - cp 'T' - ret z - ld hl,(HILOD) - cp 'H' - ret z - ld hl,(MAXLOD) - cp 'M' - ret z - ld hl,TPA - cp 'L' - ret z - ld hl,(offs.@) - cp '@' - ret z - ld hl,(OFFS.pc) - cp '$' - ret z - cp '-' - jr z,fact_factneg - cp '~' - jr z,fact_factinv - cp '+' - jr z,fact_factor - cp '^' - jr z,fact_reg.CPU - cp 'Y' - jr z,fact_reg.Y - cp '(' - jr z,fact_mem - cp '[' - jp z,EXPR_BRCKT ;0c35 [ expression ] - cp '''' - jr z,fact_factstring - dec de + call chk.sp + call get.number + ret nc + inc de + ld hl,TOPRAM + cp 'T' + ret z + ld hl,(HILOD) + cp 'H' + ret z + ld hl,(MAXLOD) + cp 'M' + ret z + ld hl,TPA + cp 'L' + ret z + ld hl,(offs.@) + cp '@' + ret z + ld hl,(OFFS.pc) + cp '$' + ret z + cp '-' + jr z,fact_factneg + cp '~' + jr z,fact_factinv + cp '+' + jr z,fact_factor + cp '^' + jr z,fact_reg.CPU + cp 'Y' + jr z,fact_reg.Y + cp '(' + jr z,fact_mem + cp '[' + jp z,EXPR_BRCKT ;0c35 [ expression ] + cp '''' + jr z,fact_factstring + dec de scf ret fact_reg.Y: - call get.decdigit - jp c,ERROR - inc de - add a,a - ld hl,reg.Y - call ADD_HL_A - ld a,(hl) - inc hl - ld h,(hl) - ld l,a - and a + call get.decdigit + jp c,ERROR + inc de + add a,a + ld hl,reg.Y + call ADD_HL_A + ld a,(hl) + inc hl + ld h,(hl) + ld l,a + and a ret fact_factstring: - ld hl,0 + ld hl,0 l0c56h: - ld a,(de) - cp '''' - jr z,l0c62h - and a - ret z + ld a,(de) + cp '''' + jr z,l0c62h + and a + ret z l0c5dh: - ld h,l - ld l,a - inc de - jr l0c56h + ld h,l + ld l,a + inc de + jr l0c56h l0c62h: - inc de - ld a,(de) - cp '''' - jr z,l0c5dh - sub '.' - or a - ret nz - inc de - set 7,l + inc de + ld a,(de) + cp '''' + jr z,l0c5dh + sub '.' + or a + ret nz + inc de + set 7,l ret fact_reg.CPU: - call sub_1315h - jr nc,l0cbbh - ld a,(hl) - inc hl - ld h,(hl) - ld l,a - and a - bit 0,c - ret nz - ld h,000h + call sub_1315h + jr nc,l0cbbh + ld a,(hl) + inc hl + ld h,(hl) + ld l,a + and a + bit 0,c + ret nz + ld h,000h ret fact_factneg: - call fact_factor - dec hl + call fact_factor + dec hl cpl.hl: - ld a,h + ld a,h cpl - ld h,a - ld a,l + ld h,a + ld a,l cpl - ld l,a + ld l,a ret fact_factinv: - call fact_factor - jr cpl.hl + call fact_factor + jr cpl.hl fact_mem: - call EXPR1 - jr c,l0cbbh - ld a,(de) - cp ')' - jr nz,l0cbbh - inc de + call EXPR1 + jr c,l0cbbh + ld a,(de) + cp ')' + jr nz,l0cbbh + inc de comst - ld a,(hl) - inc hl ; - ld h,(hl) ; + ld a,(hl) + inc hl ; + ld h,(hl) ; comend - ld l,a - ld a,(de) - inc de - cp '.' - ret z - dec de - xor a - ld h,a + ld l,a + ld a,(de) + inc de + cp '.' + ret z + dec de + xor a + ld h,a ret EXPR_BRCKT: - call EXPR1 - jr c,l0cbbh - ld a,(de) - cp ']' - inc de - ret z + call EXPR1 + jr c,l0cbbh + ld a,(de) + cp ']' + inc de + ret z l0cbbh: - jp ERROR + jp ERROR get.number: - call get.hexdigit - ret c - push de + call get.hexdigit + ret c + push de l0cc3h: - inc de - call get.hexdigit - jr nc,l0cc3h - pop de - cp '.' - jr z,l0d04h - cp '"' - jr z,l0ce9h - ld hl,0 + inc de + call get.hexdigit + jr nc,l0cc3h + pop de + cp '.' + jr z,l0d04h + cp '"' + jr z,l0ce9h + ld hl,0 l0cd5h: - call get.hexdigit - jr c,l0ce4h - add hl,hl - add hl,hl - add hl,hl - add hl,hl - call ADD_HL_A - inc de - jr l0cd5h + call get.hexdigit + jr c,l0ce4h + add hl,hl + add hl,hl + add hl,hl + add hl,hl + call ADD_HL_A + inc de + jr l0cd5h l0ce4h: - xor 'H' - ret nz - inc de + xor 'H' + ret nz + inc de ret l0ce9h: - ld hl,0 + ld hl,0 l0cech: - call get.decdigit + call get.bindigit l0cefh: - inc de - jr c,l0cf8h - add hl,hl - call ADD_HL_A - jr l0cech + inc de + jr c,l0cf8h + add hl,hl + call ADD_HL_A + jr l0cech l0cf8h: - cp '"' - jp nz,ERROR - call get.decdigit - jr nc,l0cefh - or a + cp '"' + jp nz,ERROR + call get.bindigit + jr nc,l0cefh + or a ret l0d04h: - ld hl,0 + ld hl,0 l0d07h: - call get.decdigit - inc de - jr c,l0d1ah - push bc - add hl,hl ;0d0e hl *= 10 - ld b,h - ld c,l - add hl,hl - add hl,hl - add hl,bc - pop bc - call ADD_HL_A - jr l0d07h + call get.decdigit + inc de + jr c,l0d1ah + push bc + add hl,hl ;0d0e hl *= 10 + ld b,h + ld c,l + add hl,hl + add hl,hl + add hl,bc + pop bc + call ADD_HL_A + jr l0d07h l0d1ah: - cp '.' - ret z - jp ERROR + cp '.' + ret z + jp ERROR sub_0d20h: - ld a,(de) - cp 05bh - jr l0d28h + ld a,(de) + cp 05bh + jr l0d28h get.hexdigit: - ld a,(de) + ld a,(de) sub_0d26h: - cp 'F'+1 + cp 'F'+1 l0d28h: ccf - ret c - cp 'A' - jr c,l0d32h - sub 'A'-10 + ret c + cp 'A' + jr c,l0d32h + sub 'A'-10 ret get.decdigit: - ld a,(de) + ld a,(de) l0d32h: - cp '9'+1 - jr l0d39h + cp '9'+1 + jr l0d39h get.bindigit: - ld a,(de) - cp '1'+1 + ld a,(de) + cp '1'+1 l0d39h: ccf - ret c - cp '0' - ret c - sub '0' + ret c + cp '0' + ret c + sub '0' ret l0d41h: - call assert_eol + call assert_eol prnt_cpustat: - call prnt_f - call outbl2 - ld hl,b_0x0DFD_start - ld de,b_0x0E1D_start - ld b,006h + call prnt_f + call outbl2 + ld hl,b_0x0DFD_start + ld de,b_0x0E1D_start + ld b,006h l0d52h: - call prnt_regs - djnz l0d52h - push hl - push de - ld iy,(REG.PC) - call sub_1f77h + call prnt_regs + djnz l0d52h + push hl + push de + ld iy,(REG.PC) + call sub_1f77h exx - ex af,af' - call CRLF - call prnt_f2 - call outbl2 - pop de - pop hl - ld b,007h + ex af,af' + call CRLF + call prnt_f2 + call outbl2 + pop de + pop hl + ld b,007h l0d6fh: - call prnt_regs - djnz l0d6fh + call prnt_regs + djnz l0d6fh exx - ex af,af' - and a - jr z,l0d7fh - call outbl6 - call sub_1f5bh + ex af,af' + and a + jr z,l0d7fh + call outbl6 + call sub_1f5bh l0d7fh: - jp crlf + jp crlf prnt_f: - ld a,(reg.f) - call prnt_flags - ld a,(reg.iff) - cp 0f3h - jp z,outbl - ld a,'E' - jp outchar + ld a,(reg.f) + call prnt_flags + ld a,(reg.iff) + cp 0f3h + jp z,outbl + ld a,'E' + jp outchar prnt_f2: - ld a,(reg.f2) - call prnt_flags - jp outbl + ld a,(reg.f2) + call prnt_flags + jp outbl prnt_flags: - ld b,a - ld a,'S' - call sub_0dbeh - ld a,'Z' - call sub_0dbeh - rl b - ld a,'H' - call sub_0dbeh - rl b - ld a,'V' - call sub_0dbeh - ld a,'N' - call sub_0dbeh - ld a,'C' + ld b,a + ld a,'S' + call sub_0dbeh + ld a,'Z' + call sub_0dbeh + rl b + ld a,'H' + call sub_0dbeh + rl b + ld a,'V' + call sub_0dbeh + ld a,'N' + call sub_0dbeh + ld a,'C' sub_0dbeh: - rl b - jp c,OUTCHAR - jp OUTBL + rl b + jp c,OUTCHAR + jp OUTBL prnt_regs: - push bc - push de - call PSTR - ld a,'=' - call OUTCHAR - ex (sp),hl - ld e,(hl) - inc hl - ld d,(hl) - inc hl - ld a,(hl) - inc hl - push hl - and a - jr z,l0df2h - push af - ld a,(de) - ld l,a - inc de - ld a,(de) - ld h,a - pop af - dec a - jr z,l0dedh - call out.hl.@ - call z,outbl6 - jr l0df6h + push bc + push de + call PSTR + ld a,'=' + call OUTCHAR + ex (sp),hl + ld e,(hl) + inc hl + ld d,(hl) + inc hl + ld a,(hl) + inc hl + push hl + and a + jr z,l0df2h + push af + ld a,(de) + ld l,a + inc de + ld a,(de) + ld h,a + pop af + dec a + jr z,l0dedh + call out.hl.@ + call z,outbl6 + jr l0df6h l0dedh: - call out.hl - jr l0df6h + call out.hl + jr l0df6h l0df2h: - ld a,(de) - call out.hex + ld a,(de) + call out.hex l0df6h: - call OUTBL - pop de - pop hl - pop bc + call OUTBL + pop de + pop hl + pop bc ret b_0x0DFD_start: @@ -1419,234 +1425,234 @@ b_0x0DFD_start: DB 0 b_0x0E1D_start: - defw reg.a - defb 000h - defw reg.c - defb 001h - defw reg.e - defb 001h - defw reg.l - defb 001h - defw reg.sp - defb 001h - defw reg.pc - defb 002h - defw reg.a2 - defb 000h - defw reg.c2 - defb 001h - defw reg.e2 - defb 001h - defw reg.l2 - defb 001h - defw reg.ix - defb 001h - defw reg.iy - defb 001h - defw reg.i + defw reg.a + defb 000h + defw reg.c + defb 001h + defw reg.e + defb 001h + defw reg.l + defb 001h + defw reg.sp + defb 001h + defw reg.pc + defb 002h + defw reg.a2 + defb 000h + defw reg.c2 + defb 001h + defw reg.e2 + defb 001h + defw reg.l2 + defb 001h + defw reg.ix + defb 001h + defw reg.iy + defb 001h + defw reg.i dw 0 CMD.G: - sub a - ld (TCFLG),a - ld (XA747),a - call EXPR - jr c,l0e54h - ld (REG.PC),hl + sub a + ld (TCFLG),a + ld (XA747),a + call EXPR + jr c,l0e54h + ld (REG.PC),hl l0e54h: - call SKIPBL - jp z,l1183h - cp ';' - jp nz,ERROR - inc de - ld a,002h - call sub_0f24h - jp l1183h + call SKIPBL + jp z,l1183h + cp ';' + jp nz,ERROR + inc de + ld a,002h + call sub_0f24h + jp l1183h sub_0e68h: - ld b,BP_CNT - ld ix,bp_tab + ld b,BP_CNT + ld ix,bp_tab l0e6eh: - ld a,(ix+000h) - and 0f1h - ld (ix+000h),a - call sub_11c5h - ld de,BP_SIZE - add ix,de - djnz l0e6eh + ld a,(ix+000h) + and 0f1h + ld (ix+000h),a + call sub_11c5h + ld de,BP_SIZE + add ix,de + djnz l0e6eh ret CMD.B: - call SKIPBL - jr z,l0ecbh - inc de - cp 'X' - jr z,l0e91h - dec de - ld a,001h - jp sub_0f24h + call SKIPBL + jr z,l0ecbh + inc de + cp 'X' + jr z,l0e91h + dec de + ld a,001h + jp sub_0f24h l0e91h: - call SKIPBL - jr z,l0ea6h + call SKIPBL + jr z,l0ea6h l0e96h: - call EXPR - jp c,assert_eol - push de - call sub_0ea7h - pop de - call skip_to_nextarg - jr l0e96h + call EXPR + jp c,assert_eol + push de + call sub_0ea7h + pop de + call skip_to_nextarg + jr l0e96h l0ea6h: scf sub_0ea7h: - ld b,BP_CNT - ld ix,bp_tab + ld b,BP_CNT + ld ix,bp_tab l0eadh: - push af - jr c,l0ebbh - ld e,(ix+002h) - ld d,(ix+003h) - call CP.HL.DE - jr nz,l0ec2h + push af + jr c,l0ebbh + ld e,(ix+002h) + ld d,(ix+003h) + call CP.HL.DE + jr nz,l0ec2h l0ebbh: - ld (ix+000h),000h - call sub_11c5h + ld (ix+000h),000h + call sub_11c5h l0ec2h: - ld de,BP_SIZE - add ix,de - pop af - djnz l0eadh + ld de,BP_SIZE + add ix,de + pop af + djnz l0eadh ret l0ecbh: - ld b,BP_CNT - ld ix,bp_tab + ld b,BP_CNT + ld ix,bp_tab l0ed1h: - bit 0,(ix+000h) - jr z,l0f1ch - ld a,'R' - bit 4,(ix+000h) - jr nz,l0ee1h - ld a,' ' + bit 0,(ix+000h) + jr z,l0f1ch + ld a,'R' + bit 4,(ix+000h) + jr nz,l0ee1h + ld a,' ' l0ee1h: - call OUTCHAR - call OUTBL - ld l,(ix+002h) - ld h,(ix+003h) - call out.hl.@ - call outbl2 - ld a,':' - call OUTCHAR - ld l,(ix+004h) - ld h,(ix+005h) - call out.hl - ld l,(ix+006h) - ld h,(ix+007h) - ld a,h - or l - jr z,l0f19h - call outbl4 - ld a,'I' - call OUTCHAR - call outbl2 - call PSTR + call OUTCHAR + call OUTBL + ld l,(ix+002h) + ld h,(ix+003h) + call out.hl.@ + call outbl2 + ld a,':' + call OUTCHAR + ld l,(ix+004h) + ld h,(ix+005h) + call out.hl + ld l,(ix+006h) + ld h,(ix+007h) + ld a,h + or l + jr z,l0f19h + call outbl4 + ld a,'I' + call OUTCHAR + call outbl2 + call PSTR l0f19h: - call CRLF + call CRLF l0f1ch: - ld de,BP_SIZE - add ix,de - djnz l0ed1h + ld de,BP_SIZE + add ix,de + djnz l0ed1h ret sub_0f24h: - ld b,a - call SKIPBL - ret z - cp 'R' - jr nz,l0f30h - inc de - set 4,b + ld b,a + call SKIPBL + ret z + cp 'R' + jr nz,l0f30h + inc de + set 4,b l0f30h: - push bc - call EXPR - jp c,ERROR - pop bc - bit 0,b - push bc - push de - push hl - call nz,sub_0ea7h - pop hl - call sub_0f68h - pop de - ld (ix+002h),l - ld (ix+003h),h - call sub_0f80h - ld (ix+004h),l - ld (ix+005h),h - call sub_0f91h - ld (ix+006h),l - ld (ix+007h),h - call skip_to_nextarg - pop af - ld (ix+000h),a - and 00fh - jr sub_0f24h + push bc + call EXPR + jp c,ERROR + pop bc + bit 0,b + push bc + push de + push hl + call nz,sub_0ea7h + pop hl + call sub_0f68h + pop de + ld (ix+002h),l + ld (ix+003h),h + call sub_0f80h + ld (ix+004h),l + ld (ix+005h),h + call sub_0f91h + ld (ix+006h),l + ld (ix+007h),h + call skip_to_nextarg + pop af + ld (ix+000h),a + and 00fh + jr sub_0f24h sub_0f68h: - ld b,BP_CNT - ld ix,bp_tab + ld b,BP_CNT + ld ix,bp_tab l0f6eh: - ld a,(ix+000h) - and 00fh - ret z - push bc - ld bc,BP_SIZE - add ix,bc - pop bc - djnz l0f6eh - jp ERROR + ld a,(ix+000h) + and 00fh + ret z + push bc + ld bc,BP_SIZE + add ix,bc + pop bc + djnz l0f6eh + jp ERROR sub_0f80h: - call SKIPBL - ld hl,1 - cp 03ah - ret nz - inc de - call EXPR - jp c,ERROR + call SKIPBL + ld hl,1 + cp 03ah + ret nz + inc de + call EXPR + jp c,ERROR ret sub_0f91h: - call SKIPBL - cp 049h - ld hl,0 - ret nz - inc de - call SKIPBL - push de - call EXPR - jp c,ERROR - ex de,hl - pop de - push de - sbc hl,de - ld b,h - ld c,l - ld hl,(sexp1) - push hl - add hl,bc - ld de,sexpbufe - call CP.HL.DE - jp nc,ERROR - pop hl - ld (sexp2),hl - pop de - ex de,hl + call SKIPBL + cp 049h + ld hl,0 + ret nz + inc de + call SKIPBL + push de + call EXPR + jp c,ERROR + ex de,hl + pop de + push de + sbc hl,de + ld b,h + ld c,l + ld hl,(sexp1) + push hl + add hl,bc + ld de,sexpbufe + call CP.HL.DE + jp nc,ERROR + pop hl + ld (sexp2),hl + pop de + ex de,hl ldir - xor a - ld (de),a - inc de - ex de,hl - ld (sexp1),hl - ld hl,(sexp2) + xor a + ld (de),a + inc de + ex de,hl + ld (sexp1),hl + ld hl,(sexp2) ret bpddtz: @@ -1796,7 +1802,7 @@ l10c5h: jr z,l10e7h ld l,(ix+002h) ld h,(ix+003h) - ld a,(ddtrst) + ld a,(ddtzrst) comst cp (hl) comend @@ -1859,7 +1865,7 @@ l1144h: ld h,(ix+003h) - ld a,(ddtrst) + ld a,(ddtzrst) comst ld e,(hl) ld (hl),a @@ -2191,294 +2197,294 @@ b_0x132A_start: DC 'F' DB 0 b_0x136C_start: - if ROMSYS - defb 000h - defw uromen + if ROMSYS + defb 000h + defw uromen endif if CPU_Z180 - defb 000h - defw ucbar - defb 000h - defw ubbr + defb 000h + defw ucbar + defb 000h + defw ubbr else - defb 000h - defw ubnk + defb 000h + defw ubnk endif - defb 003h - defw reg.c2 - defb 003h - defw reg.e2 - defb 003h - defw reg.l2 - defb 003h - defw reg.c - defb 003h - defw reg.e - defb 003h - defw reg.l - defb 000h - defw reg.a2 - defb 000h - defw reg.b2 - defb 000h - defw reg.c2 - defb 000h - defw reg.d2 - defb 000h - defw reg.e2 - defb 000h - defw reg.h2 - defb 000h - defw reg.l2 - defb 000h - defw reg.a - defb 000h - defw reg.b - defb 000h - defw reg.c - defb 000h - defw reg.d - defb 000h - defw reg.e - defb 000h - defw reg.h - defb 000h - defw reg.l - defb 003h - defw reg.ix - defb 003h - defw reg.iy - defb 003h - defw reg.sp - defb 003h - defw reg.pc - defb 003h - defw reg.ix - defb 003h - defw reg.iy - defb 003h - defw reg.sp - defb 003h - defw reg.pc - defb 000h - defw reg.i - defb 000h - defw reg.f2 - defb 000h - defw reg.f + defb 003h + defw reg.c2 + defb 003h + defw reg.e2 + defb 003h + defw reg.l2 + defb 003h + defw reg.c + defb 003h + defw reg.e + defb 003h + defw reg.l + defb 000h + defw reg.a2 + defb 000h + defw reg.b2 + defb 000h + defw reg.c2 + defb 000h + defw reg.d2 + defb 000h + defw reg.e2 + defb 000h + defw reg.h2 + defb 000h + defw reg.l2 + defb 000h + defw reg.a + defb 000h + defw reg.b + defb 000h + defw reg.c + defb 000h + defw reg.d + defb 000h + defw reg.e + defb 000h + defw reg.h + defb 000h + defw reg.l + defb 003h + defw reg.ix + defb 003h + defw reg.iy + defb 003h + defw reg.sp + defb 003h + defw reg.pc + defb 003h + defw reg.ix + defb 003h + defw reg.iy + defb 003h + defw reg.sp + defb 003h + defw reg.pc + defb 000h + defw reg.i + defb 000h + defw reg.f2 + defb 000h + defw reg.f CMD.S: - ld hl,(lst.S) - call get_lastarg_def + ld hl,(lst.S) + call get_lastarg_def l13d8h: - ld (lst.S),hl - call out.hl.@ - call OUTBL + ld (lst.S),hl + call out.hl.@ + call OUTBL comst - ld a,(hl) + ld a,(hl) comend - call out.hex - call outbl2 - call INLINE - call SKIPBL - inc hl - jr z,l13d8h - dec hl - inc de - cp '.' - jp z,assert_eol - cp '-' - jr nz,l1406h - ld a,(de) - or a - dec hl - jr z,l13d8h - inc hl + call out.hex + call outbl2 + call INLINE + call SKIPBL + inc hl + jr z,l13d8h + dec hl + inc de + cp '.' + jp z,assert_eol + cp '-' + jr nz,l1406h + ld a,(de) + or a + dec hl + jr z,l13d8h + inc hl l1406h: - dec de - call get_bytes_m - jr l13d8h + dec de + call get_bytes_m + jr l13d8h CMD.@: - call assert_eol - ld hl,MSG_at - ld de,offs.@ - ld c,001h - jp l1279h + call assert_eol + ld hl,MSG_at + ld de,offs.@ + ld c,001h + jp l1279h MSG_at: dc '@' CMD.I: - ld hl,CMD.I - ld (CMD_RPT),hl - ld hl,(lst.IP) - call get_lastarg_def - ld (lst.IP),hl - ld b,h - ld c,l + ld hl,CMD.I + ld (CMD_RPT),hl + ld hl,(lst.IP) + call get_lastarg_def + ld (lst.IP),hl + ld b,h + ld c,l if CPU_Z180 - ld a,b - or a - jr nz,l1442h - ld a,c - ld hl,ucbar - cp cbar - jr z,l143fh - ld hl,ubbr - cp bbr - jr nz,l1442h + ld a,b + or a + jr nz,l1442h + ld a,c + ld hl,ucbar + cp cbar + jr z,l143fh + ld hl,ubbr + cp bbr + jr nz,l1442h l143fh: - ld a,(hl) - jr l1444h + ld a,(hl) + jr l1444h l1442h: endif - in a,(c) + in a,(c) l1444h: - push af - call out.hex - call outbl4 - pop af - call out.bin.b - jp CRLF + push af + call out.hex + call outbl4 + pop af + call out.bin.b + jp CRLF CMD.O: - ld hl,CMD.O - ld (CMD_RPT),hl - ld hl,(lst.OD) - call get_arg_def - ld a,l - ld (lst.OD),a - push af - call skip_to_nextarg - ld hl,(lst.OP) - call get_lastarg_def - ld (lst.OP),hl - ld b,h - ld c,l + ld hl,CMD.O + ld (CMD_RPT),hl + ld hl,(lst.OD) + call get_arg_def + ld a,l + ld (lst.OD),a + push af + call skip_to_nextarg + ld hl,(lst.OP) + call get_lastarg_def + ld (lst.OP),hl + ld b,h + ld c,l if CPU_Z180 - ld a,b - or a - jr nz,l1489h - ld a,c - ld hl,ucbar - cp cbar - jr z,l148dh - ld hl,ubbr - cp bbr - jr z,l148dh - cp cbr - jp z,ERROR + ld a,b + or a + jr nz,l1489h + ld a,c + ld hl,ucbar + cp cbar + jr z,l148dh + ld hl,ubbr + cp bbr + jr z,l148dh + cp cbr + jp z,ERROR l1489h: endif - pop af - out (c),a + pop af + out (c),a ret if CPU_Z180 l148dh: - pop af - ld (hl),a - ret + pop af + ld (hl),a + ret endif CMD.V: - call get_arg3 ;1490 get from, size, to + call get_arg3 ;1490 get from, size, to cmp_mem: - push bc + push bc comst - ld a,(de) - ld b,(hl) + ld a,(de) + ld b,(hl) comend - cp b - jr z,l14bah - ld c,a - call out.hl.@ - call OUTBL - ld a,b - call out.hex - call outbl2 - ld a,c - call out.hex - call OUTBL - ex de,hl - call out.hl.@ - ex de,hl - call CRLF + cp b + jr z,l14bah + ld c,a + call out.hl.@ + call OUTBL + ld a,b + call out.hex + call outbl2 + ld a,c + call out.hex + call OUTBL + ex de,hl + call out.hl.@ + ex de,hl + call CRLF l14bah: - pop bc - inc hl - inc de - dec bc - ld a,b - or c - jr nz,cmp_mem + pop bc + inc hl + inc de + dec bc + ld a,b + or c + jr nz,cmp_mem ret CMD.M: - ld a,(de) - cp 'V' - jr nz,bm_nv - inc de + ld a,(de) + cp 'V' + jr nz,bm_nv + inc de bm_nv: - push af ;14c9 save 'V' flag - call get_arg3 - push hl - push de - push bc - call CP.HL.DE - jr nc,bm_mvdown - add hl,bc - ex de,hl - add hl,bc - ex de,hl - dec hl - dec de + push af ;14c9 save 'V' flag + call get_arg3 + push hl + push de + push bc + call CP.HL.DE + jr nc,bm_mvdown + add hl,bc + ex de,hl + add hl,bc + ex de,hl + dec hl + dec de comst - lddr + lddr comend - jr bm_done + jr bm_done bm_mvdown: comst ldir comend bm_done: - pop bc - pop de - pop hl - pop af - jr z,cmp_mem ;14ed validate? + pop bc + pop de + pop hl + pop af + jr z,cmp_mem ;14ed validate? ret CMD.H: - call EXPR - jp c,l173ch - call skip_to_nextarg - push hl - call EXPR - push af - call assert_eol - pop af - ex de,hl - pop hl - jr c,l1511h - push hl - push de - add hl,de - call l1511h - pop de - pop hl - and a - sbc hl,de + call EXPR + jp c,l173ch ;no parameters, print High and Max + call skip_to_nextarg + push hl + call EXPR + push af + call assert_eol + pop af + ex de,hl + pop hl + jr c,l1511h + push hl + push de + add hl,de + call l1511h + pop de + pop hl + and a + sbc hl,de l1511h: - call out.hl ;1511 val - call outbl2 - call sub_0928h ;1517 -val - call outbl4 - call out.hl.dec ;151d dec - call outbl2 - call out.hl.decm ;1523 -dec - call outbl4 - call out.bin.w ;1529 bin - call outbl2 - ld a,l - call out.ascii - jp CRLF + call out.hl ;1511 val + call outbl2 + call sub_0928h ;1517 -val + call outbl4 + call out.hl.dec ;151d dec + call outbl2 + call out.hl.decm ;1523 -dec + call outbl4 + call out.bin.w ;1529 bin + call outbl2 + ld a,l + call out.ascii + jp CRLF CMD.Q: ld a,(de) @@ -2929,415 +2935,142 @@ sub_17cdh: b_0x17EE_start: defw l1b54h - -b_0x17F0_start: defb 088h - -b_0x17F1_start: defw l1b74h - -b_0x17F3_start: defb 080h - -b_0x17F4_start: defw l1babh - -b_0x17F6_start: defb 0a0h - -b_0x17F7_start: defw l1c14h - -b_0x17F9_start: defb 040h - -b_0x17FA_start: defw l1c38h - -b_0x17FC_start: defb 0c4h - -b_0x17FD_start: defw l1b36h - -b_0x17FF_start: defb 03fh - -b_0x1800_start: defw l1babh - -b_0x1802_start: defb 0b8h - -b_0x1803_start: defw gen.opc.ED2 - -b_0x1805_start: defb 0a9h - -b_0x1806_start: defw gen.opc.ED2 - -b_0x1808_start: defb 0b9h - -b_0x1809_start: defw gen.opc.ED2 - -b_0x180B_start: defb 0a1h - -b_0x180C_start: defw gen.opc.ED2 - -b_0x180E_start: defb 0b1h - -b_0x180F_start: defw l1b36h - -b_0x1811_start: defb 02fh - -b_0x1812_start: defw l1b36h - -b_0x1814_start: defb 027h - -b_0x1815_start: defw l1dabh - -b_0x1817_start: defb 005h - -b_0x1818_start: defw l1b36h - -b_0x181A_start: defb 0f3h - -b_0x181B_start: defw l1ca4h - -b_0x181D_start: defb 010h - -b_0x181E_start: defw l1b36h - -b_0x1820_start: defb 0fbh - -b_0x1821_start: defw l1d54h - -b_0x1823_start: defb 0e3h - -b_0x1824_start: defw l1b36h - -b_0x1826_start: defb 0d9h - -b_0x1827_start: defw l1b36h - -b_0x1829_start: defb 076h - -b_0x182A_start: defw l1cbfh - -b_0x182C_start: defb 046h - -b_0x182D_start: defw l1cf8h - -b_0x182F_start: defb 040h - -b_0x1830_start: defw l1dabh - -b_0x1832_start: defb 004h - -b_0x1833_start: defw gen.opc.ED2 - -b_0x1835_start: defb 0aah - -b_0x1836_start: defw gen.opc.ED2 - -b_0x1838_start: defb 0bah - -b_0x1839_start: defw gen.opc.ED2 - -b_0x183B_start: defb 0a2h - -b_0x183C_start: defw gen.opc.ED2 - -b_0x183E_start: defb 0b2h - -b_0x183F_start: defw l1c5eh - -b_0x1841_start: defb 0c2h - -b_0x1842_start: defw l1cabh - -b_0x1844_start: defb 020h - -b_0x1845_start: defw l1934h - -b_0x1847_start: defb 040h - -b_0x1848_start: defw gen.opc.ED2 - -b_0x184A_start: defb 0a8h - -b_0x184B_start: defw gen.opc.ED2 - -b_0x184D_start: defb 0b8h - -b_0x184E_start: defw gen.opc.ED2 - -b_0x1850_start: defb 0a0h - -b_0x1851_start: defw gen.opc.ED2 - -b_0x1853_start: defb 0b0h - -b_0x1854_start: defw gen.opc.ED2 - -b_0x1856_start: defb 044h - -b_0x1857_start: defw l1b36h - -b_0x1859_start: defb 000h - -b_0x185A_start: defw l1babh - -b_0x185C_start: defb 0b0h - -b_0x185D_start: defw gen.opc.ED2 - -b_0x185F_start: defb 0bbh - -b_0x1860_start: defw gen.opc.ED2 - -b_0x1862_start: defb 0b3h - -b_0x1863_start: defw l1d2ch - -b_0x1865_start: defb 041h - -b_0x1866_start: defw gen.opc.ED2 - -b_0x1868_start: defb 0abh - -b_0x1869_start: defw gen.opc.ED2 - -b_0x186B_start: defb 0a3h - -b_0x186C_start: defw l1ce4h - -b_0x186E_start: defb 0c1h - -b_0x186F_start: defw l1ce4h - -b_0x1871_start: defb 0c5h - -b_0x1872_start: defw l1c14h - -b_0x1874_start: defb 080h - -b_0x1875_start: defw l1c50h - -b_0x1877_start: defb 0c0h - -b_0x1878_start: defw gen.opc.ED2 - -b_0x187A_start: defb 04dh - -b_0x187B_start: defw gen.opc.ED2 - -b_0x187D_start: defb 045h - -b_0x187E_start: defw l1bd8h - -b_0x1880_start: defb 010h - -b_0x1881_start: defw l1b36h - -b_0x1883_start: defb 017h - -b_0x1884_start: defw l1bd8h - -b_0x1886_start: defb 000h - -b_0x1887_start: defw l1b36h - -b_0x1889_start: defb 007h - -b_0x188A_start: defw gen.opc.ED2 - -b_0x188C_start: defb 06fh - -b_0x188D_start: defw l1bd8h - -b_0x188F_start: defb 018h - -b_0x1890_start: defw l1b36h - -b_0x1892_start: defb 01fh - -b_0x1893_start: defw l1bd8h - -b_0x1895_start: defb 008h - -b_0x1896_start: defw l1b36h - -b_0x1898_start: defb 00fh - -b_0x1899_start: defw gen.opc.ED2 - -b_0x189B_start: defb 067h - -b_0x189C_start: defw l1cd5h - -b_0x189E_start: defb 0c7h - -b_0x189F_start: defw l1b54h - -b_0x18A1_start: defb 098h - -b_0x18A2_start: defw l1b36h - -b_0x18A4_start: defb 037h - -b_0x18A5_start: defw l1c14h - -b_0x18A7_start: defb 0c0h - -b_0x18A8_start: defw l1bd8h - -b_0x18AA_start: defb 020h - -b_0x18AB_start: defw l1bd8h - -b_0x18AD_start: defb 028h - -b_0x18AE_start: defw l1bd8h - -b_0x18B0_start: defb 038h - -b_0x18B1_start: defw l1babh - -b_0x18B3_start: defb 090h - -b_0x18B4_start: defw l1babh - -b_0x18B6_start: defb 0a8h - -b_0x18B7_start: defw A.IN0 - -b_0x18B9_start: defb 000h - -b_0x18BA_start: defw A.MLT - b_0x18BC_start: defb 04ch ld b,e @@ -3345,47 +3078,19 @@ b_0x18BC_start: b_0x18BF_start: defb 08bh - -b_0x18C0_start: defw gen.opc.ED2 - -b_0x18C2_start: defb 09bh - -b_0x18C3_start: defw gen.opc.ED2 - -b_0x18C5_start: defb 083h - -b_0x18C6_start: defw gen.opc.ED2 - -b_0x18C8_start: defb 093h - -b_0x18C9_start: defw l18fdh - -b_0x18CB_start: defb 001h - -b_0x18CC_start: defw gen.opc.ED2 - -b_0x18CE_start: defb 076h - -b_0x18CF_start: defw l191dh - -b_0x18D1_start: defb 004h - -b_0x18D2_start: defw l192ch - -b_0x18D4_start: defb 074h A.IN0: call sub_1e41h @@ -4752,6 +4457,7 @@ b_0x2108_start: ; 1 byte opcodes defb 029h defw l254bh + defb 0c7h ;216c inc r defb 004h defb 041h @@ -5052,68 +4758,44 @@ l228bh: defb 0e7h defb 000h defb 0cfh - -b_0x228E_start: defw l230ch -b_0x2290_start: defb 0f7h defb 020h defb 0cfh - -b_0x2293_start: defw l230ch -b_0x2295_start: defb 0ffh defb 038h defb 0cfh - -b_0x2298_start: defw l230ch -b_0x229A_start: defb 0e7h defb 001h defb 0e7h - -b_0x229D_start: defw l2315h -b_0x229F_start: defb 0f7h defb 021h defb 0e7h - -b_0x22A2_start: defw l2315h -b_0x22A4_start: defb 0ffh defb 039h defb 0e7h - -b_0x22A7_start: defw l2315h -b_0x22A9_start: defb 0ffh defb 064h defb 0eeh - -b_0x22AC_start: defw l2397h -b_0x22AE_start: defb 0ffh defb 074h defb 0f1h - -b_0x22B1_start: defw l2397h - -b_0x22B3_start: defb 000h + l22b4h: defb 0efh defb 043h @@ -5944,7 +5626,7 @@ l27dah: ret x27ea: - ld a,(ddtrst) + ld a,(ddtzrst) comst cp (iy+000h) comend @@ -6137,7 +5819,8 @@ ddtram: ; The following 2 params are changeable by user. ; Should these moved to top ram? ; -ddtrst: rst DRSTNUM ;rst used by ddtz +ddtzrst: + rst DDTZRSTVEC ;rst used by ddtz ddtei: ei ;ints enabled/disabled while ddtz is running ret ; offs.pc: @@ -6237,9 +5920,9 @@ vartabe: ;------------------------------------------ - .phase sysram_start+stacksize + .phase sysram_start+bs$stack$size $stack: -$stcka equ $ - stacksize +$stcka equ $ - bs$stack$size curphse defl $ .dephase