page 255 .z80 extrn ?const,?conin,?cono extrn getiff extrn selbnk,@cbnk global ddtz,bpent global $stack include config.inc if CPU_Z180 include z180reg.inc include z180.lib endif BS equ 08h TAB equ 09h CR equ 0dh LF equ 0ah DEL equ 7fh CNTRX equ 'X'-'@' TPA equ 100h TOPRAM equ 0f000h MEMDUMP_CNT equ 16 ;mem dump bytes per line BP_CNT equ 12 ;number of breakbpoints ;-------------------------------------------------- ; ; copy code to common memory and execute it there comst macro call ?excom ds 1 ?lcs defl $ endm ; mark end of common code snippet comend macro ?lce defl $ ?lclen defl ?lce-?lcs org ?lcs-1 db ?lclen org ?lce ifndef ?lcmax ?lcmax defl 0 endif if ?lclen gt ?lcmax ?lcmax defl ?lclen endif endm cseg ;---------------------------------------------------------- MSG: DB 'DDT/Z - HD64180 (ROM)' DB CR,LF,0 HLPMSG: DB 'DDT/Z180 (ROM) Commands:',CR,LF DB '> @ examine/substitute the displacement register @',CR,LF DB '> A [address] Assemble',CR,LF DB '> B[X] display [or clear] all Breakpoints',CR,LF DB ' B breakp [:count] [breakp..] set Breakpoints',CR,LF DB ' BX address [address..] clear Breakpoints',CR,LF DB '>>C[N][J] [count] trace over Calls [No list] [Jumps only]',CR,LF DB ' C[N][J] W|U expression trace over Calls While|Until ...',CR,LF DB '>>D [startadr] [endadr] Display memory in hex and ascii',CR,LF DB '> G [startadr] [;breakp..] Go [to start] [temporary breakpoints]',CR,LF DB '> H [expression [expression]] compute expressions / show High/max load adr.',CR,LF DB '>>I [port] Input a byte from port',CR,LF DB '>>L [startadr] [endadr] List disassembled code',CR,LF DB '> M[V] startadr endadr destadr Move memory [and verify]',CR,LF DB '>>O [byte] [port] Output a byte to port',CR,LF DB '> Q[J] startadr endadr bytes Qery memory for byte string [Justified]',CR,LF DB '> R [displacement] Read intel hex from console [add displacemt]',CR,LF DB '> S address Substitute memory',CR,LF DB '>>T[N][J] [count] Trace [No list] [Jumps only] [count steps]',CR,LF DB ' T[N][J] W|U expression Trace While|Until expression',CR,LF DB '> V startadr endadr destadr Verify (compare) two memory areas',CR,LF DB '> X[register] eXamine [and substitute] registers',CR,LF DB '> Y[0..9] eXamine [and substitute] Y variables',CR,LF DB '> Z startadr endadr bytes Zap (fill) memory with a byte string',CR,LF DB 0 ddtz: ld sp,$stack ld a,(wstrtflg) ;check warm start flag or a ;;; jr nz,ddtz_w exx ld hl,sysramc ld de,topcodbeg ld bc,topcodend-topcodbeg ldir exx if CPU_Z180 ld a,e ld (ubbr),a endif ddtz_w: ld hl,MSG call PSTR call ddtei ; DDTZ main loop DDTZML: ld sp,$stack ld hl,l07eah ld (CMD_ERR),hl ld hl,(REG.PC) ld (OFFS.pc),hl call sub_0e68h ld hl,(CMD_RPT) ld de,DDTZML call CP.HL.DE ld a,'>' call OUTCHAR call nz,OUTCHAR call z,OUTBL call INLINE call SKIPBL jr z,exe_hl ld hl,DDTZML ld (CMD_RPT),hl inc de sub '?' jr c,ERROR cp 'Z'+1-'?' jr nc,ERROR add a,a ld hl,CMDTAB call ADD_HL_A ld a,(hl) inc hl ld h,(hl) ld l,a jr exe_hl ERROR: ld hl,(CMD_ERR) exe_hl: call CALL.HL jr DDTZML CALL.HL: jp (hl) CMDTAB: defw CMD.? ;Help defw CMD.@ ;Offset defw CMD.A ;Assemble defw CMD.B ;Breakpoint defw CMD.C ;Call defw CMD.D ;Display defw ERROR ; defw ERROR ; defw CMD.G ;Go defw CMD.H ;Hex Math defw CMD.I ;In Port defw ERROR ; defw ERROR ; defw CMD.L ;List defw CMD.M ;Move defw ERROR ; defw CMD.O ;Out Port defw ERROR ; defw CMD.Q ;Query defw CMD.R ;Read Intel Hex defw CMD.S ;Substitute defw CMD.T ;Trace defw ERROR ; defw CMD.V ;Verify defw ERROR ; defw CMD.X ;eXamine defw CMD.Y ;eXamine Y Registers defw CMD.Z ;Zap (fill) memory l07eah: ld a,'?' call OUTCHAR jp CRLF CMD.?: call assert_eol ld hl,HLPMSG call PSTR ret $ci: push hl push de push bc call ?conin pop bc pop de pop hl ret $co: push hl push de push bc ld c,a call ?cono pop bc pop de pop hl ret DELC: ld a,b or a ret z call DELC1 dec hl dec b inc c ld a,(hl) cp ' ' ret nc DELC1: push de push hl push bc ld c,BS call ?cono ld c,' ' call ?cono ld c,BS call ?cono pop bc pop hl pop de ret DELL: ld a,b ; or a ; ret z ; call DELC ; jr DELL ; INLINE: push hl ; ld hl,CI.BUF ; ld c,(hl) ; inc hl ; ld b,000h ; inc hl ; inlnxtch: ld a,c ; or a ; jr z,inl_e ; call $ci ; cp CR ; jr z,inl_e ;Accept line cp LF ; jr z,inl_e ;Accept line cp BS ; jr nz,l0844h ; call DELC ;Delete Char jr inlnxtch ; l0844h: cp DEL ; jr nz,l084dh ; call DELC ;Delete Char jr inlnxtch ; l084dh: cp CNTRX ; jr nz,l0856h ; call DELL ;Delete Line jr inlnxtch ; l0856h: cp TAB ; jr nz,l085ch ; ld a,' ' ; l085ch: ld (hl),a ; cp ' ' ; jr nc,l0869h ; ld a,'^' ;Controll characters call $co ; ld a,(hl) ; add a,'@' ; l0869h: call $co ; inc hl ; inc b ; dec c ; jr inlnxtch ; inl_e: ld hl,ci.buf+1 ; ld (hl),b ; call CRLF ; ld de,ci.buf+1 ; ld a,(de) ; ld b,a ; ld c,000h ; inc b ; l0880h: inc de ; dec b ; jr z,l08b2h ; ld a,(de) ; bit 0,c ; call z,UPCASE ; ld (de),a ; cp '''' ; jr nz,l0880h ; push de ; dec de ; ld a,(de) ; cp '''' ; jr z,l08aeh ; dec de ; ld a,(de) ; cp '^' ; jr z,l08a2h ; dec de ; ld a,(de) ; cp '^' ; jr nz,l08aeh ; l08a2h: inc de ; push bc ; call sub_0a0eh ; pop bc ; dec de ; ld a,(de) ; cp '''' ; jr z,l08afh ; l08aeh: inc c ; l08afh: pop de ; jr l0880h ; l08b2h: xor a ; ld (de),a ; ld de,ci.buf+2 ; pop hl ; ret ; UPCASE: cp 'a' ; ret c ; cp 'z'+1 ; ret nc ; and 05fh ; ret ; out.hl.@: call out.hl ; push de ; push hl ; ld de,(offs.@) ; ld a,d ; or e ; jr z,l08ddh ; call OUTBL ; ld a,'@' ; call OUTCHAR ; and a ; sbc hl,de ; call out.hl ; l08ddh: pop hl ; pop de ; ret ; out.bin.w: ld a,h ; call out.bin.b ; ld a,l ; out.bin.b: ld b,008h ; l08e7h: add a,a ; push af ; ld a,0 ; adc a,a ; call out.digit ; pop af ; djnz l08e7h ; ld a,'"' ; jp OUTCHAR ; sub_08f7h: ld a,'-' ; call OUTCHAR ; dec hl ; jp cpl.hl ; out.hl.decm: push hl ; call sub_08f7h ; db 3eh ; ld a,0E5h out.hl.dec: push hl ld b,6 ; call sub_0917h ; pop hl ; ld a,'.' ; call OUTCHAR ; l0911h: call OUTBL ; djnz l0911h ; ret ; sub_0917h: dec b push de ld de,10 call DIV_HL_DE ld a,h or l call nz,sub_0917h ld a,e pop de jr out.digit sub_0928h: push hl call sub_08f7h call out.hl pop hl ret out.hl: ld a,h call out.hex ld a,l out.hex: push af rra rra rra rra call out.digit pop af out.digit: and 00fh cp 10 jr c,l0947h add a,007h l0947h: add a,'0' jr OUTCHAR l094bh: ld a,'-' call OUTCHAR ld a,040h out.ascii: ex af,af' call outquote ex af,af' push af res 7,a cp ' ' jr nc,l0960h sub 0c0h l0960h: call OUTCHAR push af cp '''' call z,OUTCHAR pop af ex af,af' call outquote pop af or a ld a,'.' call m,OUTCHAR ex af,af' jr c,l094bh ret outquote: ld a,'''' OUTCHAR: push hl push de push bc push af and 07fh ld c,a call ?cono ld hl,CON.COL inc (hl) pop af pop bc pop de pop hl ret inchar: push hl push de push bc call ?const and a jr z,inch1 call ?conin scf inch1: pop bc pop de pop hl ret PSTR: ld c,000h l0995h: ld a,(hl) and a ret z call OUTCHAR inc c inc hl and a ret m jr l0995h outbl6: call outbl2 outbl4: call outbl2 outbl2: call OUTBL OUTBL: ld a,' ' jr OUTCHAR CRLF: call inchar ld a,CR call OUTCHAR ld a,LF call OUTCHAR ld a,000h ld (CON.COL),a jp c,DDTZML ret ADD_HL_A: add a,l ld l,a ret nc inc h ret SKIPBL0: inc de SKIPBL: ld a,(de) cp ' ' jr z,SKIPBL0 cp 009h jr z,SKIPBL0 or a ret skip_to_nextarg: call SKIPBL cp ',' ret nz inc de call SKIPBL cp a ret assert_eol: call SKIPBL ret z l09e5h: jp ERROR chk.sp: push hl push de ld hl,0 add hl,sp ld de,$stack-50 call CP.HL.DE pop de pop hl jr c,l09e5h ret CP.HL.DE: and a sbc hl,de add hl,de ret lookupch: ld b,000h l0a00h: ld a,(hl) and a ret z ld a,(de) cp (hl) jr z,l0a0bh inc hl inc b jr l0a00h l0a0bh: scf inc de ret sub_0a0eh: ld hl,b_0x132A_start ld b,07fh jr l0a17h sub_0a15h: ld b,0ffh l0a17h: inc b ld a,(hl) and a ret z call l0a27 jr nc,l0a17h res 7,b ret sub_0a23h: push bc res 7,b db 3eh ;0a26 ld a,0c5h l0a27: push bc push de l0a29h: ld a,(de) xor (hl) and 07fh jr nz,l0a41h bit 7,(hl) inc hl inc de jr z,l0a29h scf bit 7,b call z,sub_0d20h jr nc,l0a44h pop af scf pop bc ret l0a41h: call sub_0a50h l0a44h: pop de and a pop bc ret sub_0a48h: inc b l0a49h: dec b ret z call sub_0a50h jr l0a49h sub_0a50h: ld a,(hl) and a ret z l0a53h: ld a,(hl) inc hl and a ret m jr l0a53h get_arg3: call get_arg_range push hl push bc call skip_to_nextarg call get_arg ex de,hl pop bc pop hl ret sub_0a68h: call EXPR jr c,error0 ret get_arg: call sub_0a68h l0a71h: jp assert_eol get_lastarg_def: call get_arg_def jr l0a71h get_arg_def: push hl call EXPR jr c,l0a80h ex (sp),hl l0a80h: pop hl ret sub_0a82h: call sub_0a87h jr l0a71h sub_0a87h: db 0e6h ;0a87 and 037h (clear carry) get_arg_range: scf ex af,af' push bc push hl call EXPR jr nc,l0a97h ex af,af' jr c,error0 ex af,af' pop hl defb 03eh l0a97h: pop af call sub_0aa5h jr nc,l0aa3h ex af,af' pop bc ret nc error0: jp ERROR l0aa3h: pop af ret sub_0aa5h: call skip_to_nextarg cp 'S' jr nz,l0aadh inc de l0aadh: push hl push af call EXPR jr c,l0ac3h ld b,h ld c,l pop af pop hl jr z,l0ac1h ld a,c sub l ld c,a ld a,b sbc a,h ld b,a inc bc l0ac1h: and a ret l0ac3h: pop af pop hl jr z,error0 scf ret 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,l0af8h jr l0af7h do_op_ne: jr nz,l0af8h jr l0af7h do_op_le: jr z,l0af8h do_op_lt: jr c,l0af8h jr l0af7h do_op_gt: jr z,l0af7h do_op_ge: jr nc,l0af8h l0af7h: inc hl l0af8h: and a ret do_rel_op: push hl ld hl,tab_eq_le_ge call lookupch jr nc,l0b28h ld a,b or a jr z,l0b1ch ld a,(de) cp '=' jr nz,l0b11h inc de inc b inc b jr l0b1ch l0b11h: bit 0,b jr z,l0b1ch cp '>' jr nz,l0b1ch inc de ld b,005h l0b1ch: ld hl,tab_func_eqlege ld a,b add a,a call ADD_HL_A ld c,(hl) inc hl ld b,(hl) scf l0b28h: pop hl ret tab_eq_le_ge: db '=<>',0 tab_func_eqlege: defw do_op_eq defw do_op_lt defw do_op_gt defw do_op_le defw do_op_ge defw do_op_ne do_subexpr: call do_factor ret c l0b3eh: call do_binary_op push hl push bc call do_factor pop bc ex de,hl ex (sp),hl jr nc,l0b52h pop de ld a,b or c ret z jp ERROR l0b52h: ld a,b or c push bc ret nz pop bc do_op_add: add hl,de l0b58h: pop de jr l0b3eh do_op_sub: and a sbc hl,de jr l0b58h do_op_mlt: push bc if CPU_Z180 ld b,h ld c,e ld h,e ld e,l mlt bc mlt de mlt hl ld a,h add a,c add a,e ld h,a else ld b,h ld c,l ld hl,0 ld a,16 mlt_1: add hl,hl ex de,hl add hl,hl ex de,hl jr nc,mlt_2 add hl,bc mlt_2: dec a jr nz,mlt_1 endif pop bc jr l0b58h do_op_div: call DIV_HL_DE jr l0b58h do_op_mod: call DIV_HL_DE 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 ;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: 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 do_op_or: 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 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 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 fact_factor: 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 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 ret fact_factstring: ld hl,0 l0c56h: ld a,(de) cp '''' jr z,l0c62h and a ret z l0c5dh: 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 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 ret fact_factneg: call fact_factor dec hl cpl.hl: ld a,h cpl ld h,a ld a,l cpl ld l,a ret fact_factinv: call fact_factor jr cpl.hl fact_mem: call EXPR1 jr c,l0cbbh ld a,(de) cp ')' jr nz,l0cbbh inc de comst 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 ret EXPR_BRCKT: call EXPR1 jr c,l0cbbh ld a,(de) cp ']' inc de ret z l0cbbh: jp ERROR get.number: 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 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 ret l0ce9h: ld hl,0 l0cech: call get.bindigit l0cefh: inc de jr c,l0cf8h add hl,hl call ADD_HL_A jr l0cech l0cf8h: cp '"' jp nz,ERROR call get.bindigit jr nc,l0cefh or a ret l0d04h: 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 l0d1ah: cp '.' ret z jp ERROR sub_0d20h: ld a,(de) cp 05bh jr l0d28h get.hexdigit: ld a,(de) sub_0d26h: cp 'F'+1 l0d28h: ccf ret c cp 'A' jr c,l0d32h sub 'A'-10 ret get.decdigit: ld a,(de) l0d32h: cp '9'+1 jr l0d39h get.bindigit: ld a,(de) cp '1'+1 l0d39h: ccf ret c cp '0' ret c sub '0' ret l0d41h: call assert_eol prnt_cpustat: 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 exx ex af,af' call CRLF call prnt_f2 call outbl2 pop de pop hl ld b,007h l0d6fh: call prnt_regs djnz l0d6fh exx ex af,af' and a jr z,l0d7fh call outbl6 call sub_1f5bh l0d7fh: 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 prnt_f2: 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' sub_0dbeh: 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 l0dedh: call out.hl jr l0df6h l0df2h: ld a,(de) call out.hex l0df6h: call OUTBL pop de pop hl pop bc ret b_0x0DFD_start: DC 'A ' DC 'BC ' DC 'DE ' DC 'HL ' DC 'SP' DC 'PC' DC 'A''' DC 'BC''' DC 'DE''' DC 'HL''' DC 'IX' DC 'IY' DC 'I' 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 dw 0 CMD.G: 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 sub_0e68h: 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 ret CMD.B: 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 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 l0eadh: 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 l0ec2h: ld de,BP_SIZE add ix,de pop af djnz l0eadh ret l0ecbh: 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,' ' 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 l0f19h: call CRLF l0f1ch: 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 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 sub_0f68h: 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 sub_0f80h: 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 ldir xor a ld (de),a inc de ex de,hl ld (sexp1),hl ld hl,(sexp2) ret bpddtz: if ROMSYS ld h,ROMEN jr z,l0fd2h inc h l0fd2h: push hl ;save rom enable stat endif push bc push de push ix push iy ld a,i ld h,a ld l,000h push hl ;save I register if CPU_Z180 ld a,0f3h ;DI jp po,l0fe6h ld a,0fbh ;EI else ;NMOS Z80 design flaw call getiff ;return Carry set, if INTs are disabled. ld a,0f3h ;DI jr c,l0fe6h ld a,0fbh ;EI endif l0fe6h: ld (reg.iff),a ld hl,ivtab ld a,h ld i,a call ddtei ex af,af' push af exx push bc push de push hl call bp.unset if CPU_Z180 in0 a,(itc) jp p,l1017h res TRAP,a out0 (itc),a bit UFO,a jr z,l1011h ld hl,(REG.PC) dec hl ld (REG.PC),hl l1011h: ld hl,MSG_trap call PSTR l1017h: endif ld a,(XBFE8) dec a jr z,l1051h call inchar jr c,l102eh call sub_1059h and a jp z,l1183h and 083h jp z,l284ah l102eh: call sub_0e68h call prnt_cpustat jp DDTZML if CPU_Z180 MSG_trap: DB CR,LF,'Undefined opcode trap' DB CR,LF,0 endif l1051h: ld (XBFE8),a ld c,007h jp l119fh sub_1059h: ld a,080h ex af,af' sub a ld (XA747),a ld b,BP_CNT ld ix,bp_tab l1066h: ld a,(ix+000h) and 007h jr z,l107eh ld e,(ix+002h) ld d,(ix+003h) ld hl,(REG.PC) call CP.HL.DE push bc call z,sub_1087h pop bc l107eh: ld de,BP_SIZE add ix,de djnz l1066h ex af,af' ret sub_1087h: ex af,af' res 7,a ex af,af' ld e,(ix+006h) ld d,(ix+007h) ld a,d or e ld hl,0ffffh call nz,EXPR ld a,h or l jr z,l10aeh ld e,(ix+004h) ld d,(ix+005h) dec de ld a,d or e jr z,l10b9h ld (ix+004h),e ld (ix+005h),d l10aeh: bit 4,(ix+000h) ret z ld a,001h ld (XA747),a ret l10b9h: ex af,af' or (ix+000h) ex af,af' ret bp.unset: ld b,BP_CNT ld ix,bp_tab l10c5h: bit 5,(ix+000h) res 5,(ix+000h) jr z,l10e7h ld l,(ix+002h) ld h,(ix+003h) ld a,(ddtzrst) comst cp (hl) comend jr nz,l10e7h ld a,(ix+001h) comst ld (hl),a comend l10e7h: res 3,(ix+000h) ld de,BP_SIZE add ix,de djnz l10c5h ret sub_10f3h: ld b,BP_CNT ld ix,bp_tab l10f9h: ld a,(ix+000h) and 003h jr z,l110dh ld e,(ix+002h) ld d,(ix+003h) ld hl,(REG.PC) call CP.HL.DE ret z l110dh: ld de,BP_SIZE add ix,de djnz l10f9h sub a inc a ret sub_1117h: call sub_0f68h ld (ix+004h),001h ld (ix+005h),000h ld (ix+002h),l ld (ix+003h),h ld (ix+006h),000h ld (ix+007h),000h ld a,(XBFE8) and a ld a,008h jr nz,l113ah ld a,004h l113ah: ld (ix+000h),a ret bp.set: ld b,BP_CNT ld ix,bp_tab l1144h: ld a,(ix+000h) and c jr z,l117bh set 5,(ix+000h) ld l,(ix+002h) ld h,(ix+003h) ld a,(ddtzrst) comst ld e,(hl) ld (hl),a comend ld (ix+001h),e and 038h ld h,0 ld l,a ld de,bpent comst ; ld (hl),0c3h inc hl ld (hl),e inc hl ld (hl),d comend l117bh: ld de,BP_SIZE add ix,de djnz l1144h ret l1183h: sub a ld (XBFE8),a ld a,(XA747) and a call nz,prnt_cpustat call sub_10f3h ld c,007h jr nz,l119fh ld a,001h ld (XBFE8),a call sub_26e7h ld c,008h l119fh: call bp.set ld sp,$stack ;11a2 set/restore user cpu state pop hl pop de pop bc pop af exx ex af,af' pop af ld i,a pop iy pop ix pop de pop bc if ROMSYS pop hl ld a,l and M_MWI ld l,a di in0 a,(dcntl) and ~M_MWI or l ld l,a ld a,h else pop hl di endif jp $go ;11c2 common ram, switch banks and go to user prog sub_11c5h: ld a,(ix+000h) and 003h ret nz ld e,(ix+006h) ld d,(ix+007h) ld a,d or e ret z push bc ld h,d ld l,e sub a ld (ix+006h),a ld (ix+007h),a ld bc,0ffffh cpir l11e3h: push de ld de,(sexp1) call CP.HL.DE pop de jr nc,l11f9h call sub_11ffh l11f1h: ld a,(hl) ldi and a jr nz,l11f1h jr l11e3h l11f9h: ld (sexp1),de pop bc ret sub_11ffh: ld iy,bp_tab push de l1204h: ld e,(iy+006h) ld d,(iy+007h) call CP.HL.DE jr z,l1216h ld de,BP_SIZE add iy,de jr l1204h l1216h: pop de ld (iy+006h),e ld (iy+007h),d ret CMD.Y: call get.decdigit jr c,l122fh inc de push af call assert_eol pop af call sub_1248h jp l127ch l122fh: call assert_eol xor a l1233h: push af call sub_1248h call outbl4 pop af inc a bit 0,a push af call z,CRLF pop af cp LF jr c,l1233h ret sub_1248h: ld c,a ld b,0 add a,'0'+080h ld de,msg.Y+1 ld (de),a dec de ld hl,reg.Y add hl,bc add hl,bc ex de,hl ld c,003h jp l129ah CMD.X: call SKIPBL call sub_1315h jp nc,l0d41h call assert_eol ld a,b cp 01fh jr z,l12c6h cp 020h jr z,l12b6h ex de,hl ld hl,b_0x132A_start call sub_0a48h l1279h: call l129ah l127ch: call OUTBL push de push bc call INLINE call SKIPBL jr z,l1297h call get_arg ld b,h ld c,l pop af pop hl ld (hl),c bit 0,a ret z inc hl ld (hl),b ret l1297h: pop af pop hl ret l129ah: ld b,c call PSTR ld a,'=' call OUTCHAR ld a,(de) bit 0,b jp z,out.hex ld l,a inc de ld a,(de) dec de ld h,a bit 1,b jp z,out.hl jp out.hl.@ l12b6h: call prnt_f ld a,0f3h ld (reg.iff),a scf call sub_12d1h ld (reg.f),a ret l12c6h: call prnt_f2 and a call sub_12d1h ld (reg.f2),a ret sub_12d1h: ex af,af' ld b,000h call outbl call assert_eol call inline l12ddh: call skipbl ld a,b ret z push bc ld hl,tab_pr_flags call lookupch jp nc,error ld a,b cp 008h jr z,l12feh inc b ld a,001h jr l12f7h l12f6h: rlca l12f7h: djnz l12f6h pop bc or b ld b,a jr l12ddh l12feh: ex af,af' jp nc,ERROR ex af,af' ld a,0FBh ld (reg.iff),a pop bc jr l12ddh tab_pr_flags: db 'CNV H ZSE' db 0 sub_1315h: call sub_0a0eh ret nc ld a,b add a,b add a,b ld hl,b_0x136C_start call ADD_HL_A ld c,(hl) inc hl ld a,(hl) inc hl ld h,(hl) ld l,a scf ret b_0x132A_start: if ROMSYS DC 'ROMSEL' endif if CPU_Z180 DC 'CBAR' DC 'BBR' else DC 'BNK' endif 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 'F''' DC 'F' DB 0 b_0x136C_start: if ROMSYS defb 000h defw uromen endif if CPU_Z180 defb 000h defw ucbar defb 000h defw ubbr else 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 CMD.S: ld hl,(lst.S) call get_lastarg_def l13d8h: ld (lst.S),hl call out.hl.@ call OUTBL comst 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 l1406h: dec de call get_bytes_m jr l13d8h CMD.@: 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 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 l143fh: ld a,(hl) jr l1444h l1442h: endif in a,(c) l1444h: 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 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 l1489h: endif pop af out (c),a ret if CPU_Z180 l148dh: pop af ld (hl),a ret endif CMD.V: call get_arg3 ;1490 get from, size, to cmp_mem: push bc comst 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 l14bah: 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 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 comst lddr comend jr bm_done bm_mvdown: comst ldir comend bm_done: pop bc pop de pop hl pop af jr z,cmp_mem ;14ed validate? ret CMD.H: 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 CMD.Q: ld a,(de) sub 'J' ld (lst.Qj),a jr nz,l153fh inc de l153fh: call get_arg_range push bc push hl call sub_15a7h pop hl l1548h: call sub_1594h jr nz,l1562h push bc push hl ld a,(lst.Qj) or a jr nz,l1559h ld bc,-8 add hl,bc l1559h: ld bc,MEMDUMP_CNT and a call memdump pop hl pop bc l1562h: inc hl ex (sp),hl dec hl ld a,h or l ex (sp),hl jr nz,l1548h pop bc ret CMD.Z: call get_arg_range push bc push hl call sub_15a7h ld a,b pop hl pop bc push hl ex de,hl l1579h: push af ld a,(hl) comst ld (de),a comend pop af inc de cpi jp po,l1592h dec a jr nz,l1579h pop hl comst ldir comend ret l1592h: pop hl ret sub_1594h: push hl push de push bc l1597h: ld a,(de) comst cp (hl) comend jr nz,l15a3h inc de inc hl djnz l1597h l15a3h: pop bc pop de pop hl ret sub_15a7h: ld hl,ci.buf+1 call get_bytes ld de,ci.buf+1 and a sbc hl,de ld b,l ret nz jp ERROR get_bytes: db 0e6h ;15b8 and 037h (clear carry, skip next opc) get_bytes_m: scf l15bah: push af call skip_to_nextarg cp 'W' jr nz,l15d9h inc de push hl call sub_0a68h ex de,hl pop bc pop af push af push bc ex (sp),hl jr nc,l15d3h comst l15d3h: ld (hl),e comend inc hl ld c,d pop de jr l15e5h l15d9h: cp '''' jr z,l15f1h push hl call EXPR ld c,l pop hl jr c,l1626h l15e5h: pop af push af jr nc,l15edh comst l15edh: ld (hl),c comend inc hl jr l161eh l15f1h: inc de ld a,(de) cp '''' jr z,l1607h or a jr z,l1626h l15fah: ld c,a pop af push af jr nc,l1603h comst l1603h: ld (hl),c comend inc hl jr l15f1h l1607h: inc de ld a,(de) cp '''' jr z,l15fah cp '.' jr nz,l161eh inc de dec hl pop af push af jr nc,l161bh comst l161bh: set 7,(hl) comend inc hl l161eh: pop af jr nc,l15bah ld (lst.S),hl jr l15bah l1626h: pop af ret nc ld (lst.S),hl ret CMD.D: ld hl,CMD.D ld (CMD_RPT),hl ld hl,(lst.D) ld bc,00080h call sub_0a82h scf memdump: push bc push de push hl ex af,af' l1640h: call out.hl.@ call z,outbl2 call OUTBL ld de,0 l164ch: comst ld a,(hl) comend inc hl call out.hex call OUTBL dec bc inc e ld a,e cp 010h jr z,l1668h and 003h call z,OUTBL ld a,b or c jr nz,l164ch l1668h: call OUTBL and a sbc hl,de l166eh: comst ld a,(hl) comend call sub_168fh call OUTCHAR inc hl dec e jr nz,l166eh ex af,af' jr nc,l1683h ld (lst.D),hl l1683h: ex af,af' call CRLF ld a,b or c jr nz,l1640h pop hl pop de pop bc ret sub_168fh: and 07fh cp 07fh jr z,l1698h cp 020h ret nc l1698h: ld a,02eh ret ; Read Intel Hex File from console. CMD.R: ld hl,0 call get_lastarg_def ;169e get offset from command line push hl ld hl,0 ld (HILOD),hl w_recstart: call i.getchar jr z,l16deh cp ':' jr nz,w_recstart ld c,0 ;16b1 init checksum call i.gethexbyte ;16b3 record len ld b,a call i.gethexbyte ;16b7 address high ld h,a call i.gethexbyte ;16bb address low ld l,a call i.gethexbyte ;16bf record type (ignored) ld a,b and a ;16c3 record len == 0? jr z,l16deh l16c6h: call i.gethexbyte pop de ;16c9 offset push de push hl add hl,de call i.storebyte pop hl inc hl djnz l16c6h ;16d2 repeat for record len call i.gethexbyte ;16d4 checksum ld a,c and a jp nz,ERROR ;16d9 exit if checksum error jr w_recstart ;16dc next record l16deh: pop hl call i.gethexbyte jp l173fh i.gethexbyte: call sub_16f6h rlca rlca rlca rlca ld d,a call sub_16f6h add a,d ld d,a add a,c ld c,a ld a,d ret sub_16f6h: call i.getchar jr z,l16ffh call sub_0d26h ret nc l16ffh: jp ERROR i.getchar: call $ci cp 01ah ret i.storebyte: push af push de ld de,TPA ;170a lowest allowed load address call CP.HL.DE jp c,ERROR ld de,$stcka ;1713 highest allowed load address call CP.HL.DE jp nc,ERROR ld de,(HILOD) call CP.HL.DE jr c,l1728h ld (HILOD),hl l1728h: ld de,(MAXLOD) call CP.HL.DE jr c,l1734h ld (MAXLOD),hl l1734h: pop de pop af comst ld (hl),a ;173a store byte comend ret l173ch: call assert_eol l173fh: ld hl,MSG_high call PSTR ld hl,(HILOD) call out.hl ld hl,MSG_max call PSTR ld hl,(MAXLOD) call out.hl jp CRLF MSG_high: DC 'High = ' MSG_max: DC ' Max = ' CMD.A: ld hl,(lst.A) call get_lastarg_def push hl pop iy ld hl,l17c4h ld (CMD_ERR),hl ld (XB068),sp l177ch: push iy pop hl ld (lst.A),hl ld (OFFS.pc),hl push hl call sub_1f3fh pop iy ld c,b ld de,(offs.@) ld a,d or e ld b,011h jr z,l1798h ld b,019h l1798h: call OUTBL ld a,(CON.COL) cp b jr c,l1798h push bc call INLINE pop bc call SKIPBL cp '.' ret z cp '-' jr nz,l17b6h ld iy,(XB06C) jr l177ch l17b6h: and a call nz,sub_17cdh ld (XB06C),iy ld b,0 add iy,bc jr l177ch l17c4h: call l07eah ld sp,(XB068) jr l177ch sub_17cdh: call SKIPBL ld hl,t_MNEMONICS call sub_0a15h jp nc,ERROR call SKIPBL push de ld a,b add a,b add a,b ld hl,b_0x17EE_start call ADD_HL_A ld e,(hl) inc hl ld d,(hl) inc hl ld b,(hl) ex de,hl pop de jp (hl) b_0x17EE_start: defw l1b54h defb 088h defw l1b74h defb 080h defw l1babh defb 0a0h defw l1c14h defb 040h defw l1c38h defb 0c4h defw l1b36h defb 03fh defw l1babh defb 0b8h defw gen.opc.ED2 defb 0a9h defw gen.opc.ED2 defb 0b9h defw gen.opc.ED2 defb 0a1h defw gen.opc.ED2 defb 0b1h defw l1b36h defb 02fh defw l1b36h defb 027h defw l1dabh defb 005h defw l1b36h defb 0f3h defw l1ca4h defb 010h defw l1b36h defb 0fbh defw l1d54h defb 0e3h defw l1b36h defb 0d9h defw l1b36h defb 076h defw l1cbfh defb 046h defw l1cf8h defb 040h defw l1dabh defb 004h defw gen.opc.ED2 defb 0aah defw gen.opc.ED2 defb 0bah defw gen.opc.ED2 defb 0a2h defw gen.opc.ED2 defb 0b2h defw l1c5eh defb 0c2h defw l1cabh defb 020h defw l1934h defb 040h defw gen.opc.ED2 defb 0a8h defw gen.opc.ED2 defb 0b8h defw gen.opc.ED2 defb 0a0h defw gen.opc.ED2 defb 0b0h defw gen.opc.ED2 defb 044h defw l1b36h defb 000h defw l1babh defb 0b0h defw gen.opc.ED2 defb 0bbh defw gen.opc.ED2 defb 0b3h defw l1d2ch defb 041h defw gen.opc.ED2 defb 0abh defw gen.opc.ED2 defb 0a3h defw l1ce4h defb 0c1h defw l1ce4h defb 0c5h defw l1c14h defb 080h defw l1c50h defb 0c0h defw gen.opc.ED2 defb 04dh defw gen.opc.ED2 defb 045h defw l1bd8h defb 010h defw l1b36h defb 017h defw l1bd8h defb 000h defw l1b36h defb 007h defw gen.opc.ED2 defb 06fh defw l1bd8h defb 018h defw l1b36h defb 01fh defw l1bd8h defb 008h defw l1b36h defb 00fh defw gen.opc.ED2 defb 067h defw l1cd5h defb 0c7h defw l1b54h defb 098h defw l1b36h defb 037h defw l1c14h defb 0c0h defw l1bd8h defb 020h defw l1bd8h defb 028h defw l1bd8h defb 038h defw l1babh defb 090h defw l1babh defb 0a8h defw A.IN0 defb 000h defw A.MLT b_0x18BC_start: defb 04ch ld b,e dec de b_0x18BF_start: defb 08bh defw gen.opc.ED2 defb 09bh defw gen.opc.ED2 defb 083h defw gen.opc.ED2 defb 093h defw l18fdh defb 001h defw gen.opc.ED2 defb 076h defw l191dh defb 004h defw l192ch defb 074h A.IN0: call sub_1e41h jr nc,l1931h cp 006h jr z,l1931h rlca rlca rlca add a,b ld b,a call sub_1ed1h call sub_1e06h l18e9h: call assert_eol comst ld (iy+000h),0edh ld (iy+001h),b ld (iy+002h),l comend ld c,003h ret l18fdh: call sub_1e06h call sub_1ed1h call sub_1e41h jr nc,l1931h cp 006h jr z,l1931h rlca rlca rlca add a,b ld b,a jr l18e9h A.MLT: call sub_1e2eh jr nc,l1931h add a,b ld b,a jp gen.opc.ED2 l191dh: call sub_1e41h jr nc,l192ah rlca rlca rlca add a,b ld b,a jp gen.opc.ED2 l192ah: ld b,064h l192ch: call sub_1e12h jr l18e9h l1931h: jp ERROR l1934h: call sub_1e41h jp c,l19bfh call sub_1e68h jp c,l1a64h call sub_1e2eh jp c,l1a93h call sub_1e50h jp c,l1af0h ld a,(de) cp 049h jp z,l1b0ch cp 052h jp z,l1b14h cp 028h jp nz,ERROR inc de call sub_1e2eh jp c,l1b23h call tst_EXPR call sub_1ed8h call sub_1ed1h call sub_1e2eh jr c,l19adh call sub_1e50h jr nc,l1991h ld b,022h l1978h: call assert_eol ld a,(pfx.IXY) l197eh: comst ld (iy+000h),a ld (iy+001h),b ld (iy+002h),l ld (iy+003h),h comend ld c,004h ret l1991h: ld a,(de) cp 041h jp nz,ERROR inc de ld b,032h l199ah: call assert_eol comst ld (iy+000h),b ld (iy+001h),l ld (iy+002h),h comend ld c,003h ret l19adh: cp 020h jr z,l19bbh add a,043h ld b,a l19b4h: call assert_eol ld a,0edh jr l197eh l19bbh: ld b,022h jr l199ah l19bfh: ld b,a call sub_1ed1h call sub_1e41h jr nc,l19dbh push af ld a,b rlca rlca rlca ld b,a pop af add a,b add a,040h cp 076h jp z,ERROR l19d7h: ld b,a jp l1b36h l19dbh: call sub_1e68h jr nc,l1a02h ld a,b rlca rlca rlca add a,046h cp 076h jp z,ERROR l19ebh: ld b,a call assert_eol ld a,(pfx.IXY) comst ld (iy+000h),a ld (iy+001h),b ld (iy+002h),c comend ld c,003h ret l1a02h: ld a,(de) cp 'I' jr z,l1a15h cp 'R' jr nz,l1a21h ld a,b cp 007h jp nz,ERROR ld b,05fh jr l1a1dh l1a15h: ld a,b cp 007h jp nz,ERROR ld b,057h l1a1dh: inc de jp gen.opc.ED2 l1a21h: cp '(' jr z,l1a3fh call sub_1e12h ld a,b ;1a28 ld r,nn rlca rlca rlca add a,006h l1a2eh: ld b,a l1a2fh: call assert_eol comst ld (iy+000h),b ld (iy+001h),l comend ld c,002h ret l1a3fh: inc de ld a,b cp 007h jp nz,ERROR call sub_1e2eh jr nc,l1a59h cp 030h jp nc,ERROR add a,00ah ld b,a call sub_1ed8h jp l1b36h l1a59h: call tst_EXPR call sub_1ed8h ld b,03ah jp l199ah l1a64h: call sub_1ed1h call sub_1e41h jr nc,l1a76h cp 006h jp z,ERROR add a,070h jp l19ebh l1a76h: call sub_1e12h call assert_eol ld a,(pfx.IXY) comst ld (iy+000h),a ;1a83 dd/fd ld (iy+001h),036h ld (iy+002h),c ;1a8a displacement ld (iy+003h),l ;1a8d nn comend ld c,4 ret l1a93h: ld b,a call sub_1ed1h ld hl,t_HL.AF call sub_0a23h jr c,l1abeh call sub_1e50h jr nc,l1ac7h ld a,b cp 030h jr nz,l1b20h ld b,0f9h l1aabh: call assert_eol ld a,(pfx.IXY) comst ld (iy+000h),a ld (iy+001h),b comend ld c,002h ret l1abeh: ld a,b cp 030h jr nz,l1b20h ld b,0f9h jr l1b36h l1ac7h: ld a,(de) cp 028h jr nz,l1ae3h inc de call tst_EXPR call sub_1ed8h ld a,b cp 020h jr z,l1adeh add a,04bh ld b,a jp l19b4h l1adeh: ld b,02ah jp l199ah l1ae3h: call tst_EXPR call assert_eol ld a,001h add a,b ld b,a jp l199ah l1af0h: call sub_1ed1h ld a,(de) cp 028h jr nz,l1b04h inc de call tst_EXPR call sub_1ed8h ld b,02ah jp l1978h l1b04h: call tst_EXPR ld b,021h jp l1978h l1b0ch: inc de call sub_1ed1h ld b,047h jr l1b1ah l1b14h: inc de call sub_1ed1h ld b,04fh l1b1ah: ld a,(de) inc de cp 041h jr z,gen.opc.ED2 l1b20h: jp ERROR l1b23h: cp 020h jr nc,l1b20h add a,002h ld b,a call sub_1ed8h call sub_1ed1h ld a,(de) cp 041h jr nz,l1b20h inc de l1b36h: call assert_eol comst ld (iy+000h),b comend ld c,001h ret gen.opc.ED2: call assert_eol comst ld (iy+000h),0edh ld (iy+001h),b comend ld c,002h ret l1b54h: ld hl,t_HL.AF call sub_0a23h jr nc,l1babh call sub_1ed1h call sub_1e2eh jp nc,ERROR push af ld a,b cp 088h ld b,04ah jr z,l1b6fh ld b,042h l1b6fh: pop af add a,b l1b71h: ld b,a jr gen.opc.ED2 l1b74h: ld hl,t_HL.AF call sub_0a23h jr c,l1b9dh call sub_1e50h jr nc,l1babh call sub_1ed1h ld hl,t_BC.DE.IX.SP ld a,(pfx.IXY) cp 0fdh jr nz,l1b91h ld hl,t_BC.DE.IY.SP l1b91h: call sub_1e2bh jp nc,ERROR add a,009h l1b99h: ld b,a jp l1aabh l1b9dh: call sub_1ed1h call sub_1e2eh jp nc,ERROR add a,009h jp l19d7h l1babh: ld a,(de) cp 041h jr nz,l1bbbh push de inc de call skip_to_nextarg jr z,l1bbah pop de jr l1bbbh l1bbah: pop af l1bbbh: call sub_1e41h jr c,l1bceh call sub_1e68h jr c,l1bd2h call sub_1e12h ld a,b add a,046h jp l1a2eh l1bceh: add a,b jp l19d7h l1bd2h: ld a,b add a,006h jp l19ebh l1bd8h: call sub_1e41h jr c,l1c01h call sub_1e68h jp nc,ERROR ld a,b add a,006h ld b,a l1be7h: call assert_eol ld a,(pfx.IXY) comst ld (iy+000h),a ld (iy+001h),0cbh ld (iy+002h),c ld (iy+003h),b comend ld c,004h ret l1c01h: add a,b l1c02h: ld b,a call assert_eol comst ld (iy+000h),0cbh ld (iy+001h),b comend ld c,002h ret l1c14h: call sub_1de6h call sub_1ed1h call sub_1e41h jr c,l1c2fh call sub_1e68h jp nc,ERROR ld a,l rlca rlca rlca add a,006h add a,b ld b,a jr l1be7h l1c2fh: add a,b ld b,a ld a,l rlca rlca rlca add a,b jr l1c02h l1c38h: push de call sub_1eb8h jr nc,l1c47h add a,b ld b,a call skip_to_nextarg jr z,l1c49h pop de push de l1c47h: ld b,0cdh l1c49h: pop af call tst_EXPR jp l199ah l1c50h: call sub_1eb8h jr nc,l1c59h add a,b ld b,a jr l1c5bh l1c59h: ld b,0c9h l1c5bh: jp l1b36h l1c5eh: push de call sub_1eb8h jr c,l1c71h l1c64h: pop de ld hl,b_0x1C97_start call sub_0a15h jr c,l1c7fh ld b,0c3h jr l1c79h l1c71h: add a,b ld b,a call skip_to_nextarg jr nz,l1c64h pop af l1c79h: call tst_EXPR jp l199ah l1c7fh: call assert_eol ld a,b and a jr nz,l1c8bh ld b,0e9h jp l1b36h l1c8bh: ld b,0ddh dec a jr z,l1c92h ld b,0fdh l1c92h: ld l,0e9h jp l1a2fh b_0x1C97_start: DC '(HL)' DC '(IX)' DC '(IY)' DB 0 l1ca4h: call skip_to_nextarg ld b,010h jr l1cb9h l1cabh: call sub_1ebfh jr c,l1cb4h ld b,018h jr l1cb9h l1cb4h: add a,b ld b,a call sub_1ed1h l1cb9h: call sub_1defh jp l1a2fh l1cbfh: call sub_1e12h ld a,l cp 003h jr nc,l1d23h and a jr z,l1cd2h ld b,056h cp 001h jr z,l1cd2h ld b,05eh l1cd2h: jp gen.opc.ED2 l1cd5h: call sub_1e12h ld a,l push af add a,b ld b,a pop af and 0c7h jr nz,l1d23h jp l1b36h l1ce4h: call sub_1e50h jr c,l1cf2h call sub_1e25h jr nc,l1d23h add a,b jp l19d7h l1cf2h: ld a,b add a,020h jp l1b99h l1cf8h: call sub_1e41h jr nc,l1d23h cp 006h jr z,l1d23h rlca rlca rlca add a,b ld b,a cp 078h jr nz,l1d1ah call sub_1ed1h call sub_1d26h jr c,l1d20h call sub_1e06h ld b,0dbh jp l1a2fh l1d1ah: call sub_1ed1h call sub_1d26h l1d20h: jp c,gen.opc.ED2 l1d23h: jp ERROR sub_1d26h: ld hl,t__C_ jp sub_0a23h l1d2ch: call sub_1d26h jr nc,l1d44h call sub_1ed1h call sub_1e41h jr nc,l1d23h cp 006h jr z,l1d23h rlca rlca rlca add a,b jp l1b71h l1d44h: call sub_1e06h call sub_1ed1h cp 041h jr nz,l1d23h inc de ld b,0d3h jp l1a2fh l1d54h: ld hl,b_0x1D80_start call sub_0a15h jp nc,ERROR ld c,b call assert_eol ld b,000h ld hl,b_0x1DA1_start add hl,bc add hl,bc ld a,(hl) comst ld (iy+000h),a comend ld c,001h inc hl ld a,(hl) and a ret z comst ld (iy+001h),a comend ld c,002h ret b_0x1D80_start: DC 'AF,AF''' l1d86h: DC 'DE,HL' DC '(SP),HL' DC '(SP),IX' DC '(SP),IY' db 000h b_0x1DA1_start: db 008h db 000h db 0ebh db 000h db 0e3h db 000h db 0ddh db 0e3h db 0fdh db 0e3h l1dabh: call sub_1e50h jr c,l1dc6h call sub_1e2eh jr c,l1dd2h call sub_1e41h jr c,l1ddfh call sub_1e68h jp nc,ERROR ld a,b add a,030h jp l19ebh l1dc6h: ld a,b ld b,023h cp 004h jr z,l1dcfh ld b,02bh l1dcfh: jp l1aabh l1dd2h: push af ld a,b ld b,003h cp 004h jr z,l1ddch ld b,00bh l1ddch: pop af jr l1de2h l1ddfh: rlca rlca rlca l1de2h: add a,b jp l19d7h sub_1de6h: call sub_1e12h ld a,l cp 008h jr nc,error1 ret sub_1defh: call tst_EXPR push bc push iy pop bc and a sbc hl,bc dec hl dec hl pop bc call sub_1e15h ld a,h xor l bit 7,a jr nz,error1 ret sub_1e06h: ld a,(de) cp 028h jr nz,sub_1e12h inc de call sub_1e12h jp sub_1ed8h sub_1e12h: call tst_EXPR sub_1e15h: ld a,h and a ret z inc a ret z jr error1 tst_EXPR: push bc call EXPR pop bc ret nc error1: jp ERROR sub_1e25h: push hl ld hl,t_BC.DE.HL.AF jr l1e32h sub_1e2bh: push hl jr l1e32h sub_1e2eh: push hl ld hl,t_BC.DE.HL.SP l1e32h: push bc call sub_0a15h jr nc,l1e3eh ld a,b rlca rlca rlca rlca scf l1e3eh: pop bc pop hl ret sub_1e41h: call SKIPBL push bc push hl ld hl,t_BCDEHL_HL_A call sub_0a15h ld a,b pop hl pop bc ret sub_1e50h: push hl push bc ld hl,t_IX.IY call sub_0a15h jr nc,l1e65h ld a,0ddh dec b jr nz,l1e61h ld a,0fdh l1e61h: ld (pfx.IXY),a scf l1e65h: pop bc pop hl ret sub_1e68h: push hl push bc ld a,(de) cp '(' jr nz,l1eb4h push de inc de ld hl,t_IX.IY call sub_0a15h jr nc,l1eb3h pop af ld a,0ddh dec b jr nz,l1e81h ld a,0fdh l1e81h: ld (pfx.IXY),a ld a,(de) cp '+' jr z,l1e95h cp ')' ld hl,0 jr z,l1eadh cp '-' jp nz,ERROR l1e95h: push af inc de call sub_1e12h ;1e97 get displacement pop af cp '+' jr z,l1ea7h ld b,h ld c,l ld hl,0 and a sbc hl,bc l1ea7h: ld a,(de) cp ')' jp nz,ERROR l1eadh: inc de pop bc ld c,l pop hl scf ret l1eb3h: pop de l1eb4h: pop bc pop hl and a ret sub_1eb8h: ld hl,t_tstfl_ZCPS ld c,007h jr l1ec4h sub_1ebfh: ld hl,t_tstfl_ZC ld c,003h l1ec4h: push bc call sub_0a15h ld a,b pop bc ret nc and c rlca rlca rlca scf ret sub_1ed1h: call skip_to_nextarg ret z l1ed5h: jp ERROR sub_1ed8h: ld a,(de) cp 029h jr nz,l1ed5h inc de ret CMD.L: ld hl,CMD.L ld (CMD_RPT),hl call EXPR jr nc,l1eedh ld hl,(lst.L) l1eedh: push hl pop iy call skip_to_nextarg call sub_0aa5h jr nc,l1f17h call assert_eol ld b,010h l1efdh: push bc push iy pop hl push hl call sub_1f3fh call CRLF pop iy ld c,b ld b,000h add iy,bc ld (lst.L),iy pop bc djnz l1efdh ret l1f17h: call assert_eol ld h,b ld l,c ld a,b or c jr nz,l1f21h dec hl l1f21h: push hl push iy pop hl push hl call sub_1f3fh call CRLF pop iy ld e,b ld d,000h add iy,de ld (lst.L),iy pop hl and a sbc hl,de ret z ret c jr l1f21h sub_1f3fh: call out.hl.@ call z,OUTBL call OUTBL sub a ld (CON.COL),a call sub_1f77h and a ret z l1f51h: call OUTBL ld a,(CON.COL) cp 010h jr c,l1f51h sub_1f5bh: ld de,(offs.@) ld a,d or e ret z ld a,'(' call OUTCHAR ld a,'@' call OUTCHAR and a sbc hl,de call out.hl ld a,')' jp OUTCHAR sub_1f77h: sub a ld (XBE03),a call sub_1f9eh jr nc,l1f91h push bc call sub_2581h ex de,hl call sub_1fdbh pop bc ld a,(XBE03) ld hl,(XBE01) scf ret l1f91h: ld hl,b_0x1F9B_start call PSTR ld b,001h sub a ret b_0x1F9B_start: DC '???' sub_1f9eh: sub a ld (is.pfx.IXY),a comst ld a,(iy+000h) comend cp 0edh jp z,disas_pfx.ED cp 0ddh jr z,l1fc5h cp 0fdh jr z,l1fc9h sub_1fb6h: comst ld a,(iy+000h) comend cp 0cbh jp z,l2061h jp l2078h l1fc5h: ld a,001h jr l1fcbh l1fc9h: ld a,002h l1fcbh: ld (is.pfx.IXY),a call sub_1fdch ret nc push bc call sub_1fb6h pop af add a,b ld b,a scf ret sub_1fdbh: jp (hl) sub_1fdch: inc iy ld hl,b_0x2011_start call sub_20bbh ld b,002h ret c ld hl,l202ch call sub_20bbh ld b,001h ret c comst ld a,(iy+000h) comend cp 0cbh jr nz,l200fh comst ld a,(iy+002h) comend cp 036h ret z and 007h cp 006h jr nz,l200fh ld b,002h scf ret l200fh: and a ret b_0x2011_start: db 034h db 035h db 036h db 046h db 04eh db 056h db 05eh db 066h db 06eh db 070h db 071h db 072h db 073h db 074h db 075h db 076h db 077h db 07eh db 086h db 08eh db 096h db 09eh db 0a6h db 0aeh db 0b6h db 0beh db 000h l202ch: db 009h db 019h db 021h db 022h db 023h db 029h db 02ah db 02bh db 039h db 0e1h db 0e3h db 0e5h db 0e9h db 0f9h db 000h disas_pfx.ED: inc iy ld hl,b_0x2200_start call sub_209dh ld b,002h ret c ld hl,l2235h call lookup_opc ld b,002h ret c ld hl,l228bh call lookup_opc ld b,003h ret c ld hl,l22b4h call lookup_opc ld b,004h ret l2061h: push iy inc iy ld a,(is.pfx.IXY) and a jr z,l206dh inc iy l206dh: ld hl,l22c9h call lookup_opc pop iy ld b,002h ret l2078h: ld hl,b_0x218B_start call lookup_opc ld b,002h ret c ld hl,b_0x20ED_start call sub_209dh ld b,001h ret c ld hl,b_0x2108_start call lookup_opc ld b,001h ret c ld hl,b_0x21D2_start call lookup_opc ret nc ld b,003h ret sub_209dh: ld a,(hl) cp 0ffh ret z comst cp (iy+000h) comend jr z,l20aeh inc hl inc hl jr sub_209dh l20aeh: inc hl ld c,(hl) ld hl,t_MNEMONICS ld b,000h add hl,bc ld de,l230bh scf ret sub_20bbh: ld a,(hl) and a ret z inc hl comst cp (iy+000h) comend jr nz,sub_20bbh scf ret lookup_opc: comst ld a,(iy+000h) comend and (hl) inc hl cp (hl) jr z,l20dfh inc hl inc hl inc hl inc hl ld a,(hl) and a jr nz,lookup_opc ret l20dfh: inc hl ld c,(hl) inc hl ld e,(hl) inc hl ld d,(hl) ld hl,t_MNEMONICS ld b,000h add hl,bc scf ret b_0x20ED_start: ; 1 byte opcodes (no parameters) db 076h ;20ed halt db 039h ;20ee db 0d9h ;20ef exx db 036h db 0f3h ;20f1 di db 02ch db 0fbh ;20f3 ei db 032h db 000h ;20f5 nop db 069h db 007h ;20f7 rlca db 09eh db 00fh ;20f9 rrca db 0adh db 017h ;20fb rla db 098h db 01fh ;20fd rra db 0a7h db 027h ;20ff daa db 026h db 02fh ;2101 cpl db 023h db 037h ;2103 scf db 0bah db 03fh ;2105 ccf db 010h db 0ffh ;2107 EOT b_0x2108_start: ; 1 byte opcodes defb 0c0h ;2108 ld r,r defb 040h defb 056h defw l22fch defb 0f8h ;210d add a,r defb 080h defb 003h defw l2305h defb 0f8h ;2112 adc a,r defb 088h defb 000h defw l2305h defb 0f8h defb 090h defb 0c9h defw l24ebh defb 0f8h defb 098h defb 0b7h defw l2305h defb 0f8h defb 0a0h defb 006h defw l24ebh defb 0f8h defb 0a8h defb 0cch defw l24ebh defb 0f8h defb 0b0h defb 06ch defw l24ebh defb 0f8h defb 0b8h defb 013h defw l24ebh defb 0c7h defb 0c0h ;2136 ret cc defb 08bh defw l2561h defb 0c7h ;213a rst defb 0c7h defb 0b4h defw l231eh defb 0ffh ;213f ret defb 0c9h defb 08bh defw l230bh defb 0cfh ;2144 pop rr defb 0c1h defb 081h defw l2546h defb 0cfh ;2149 push rr defb 0c5h defb 084h defw l2546h defb 0ffh ;214e ex (sp),hl defb 0e3h defb 034h defw l232ah defb 0ffh ;2153 jp (hl) defb 0e9h defb 052h defw l2338h defb 0ffh ;2158 ex de,hl defb 0ebh defb 034h defw l2345h defb 0ffh ;215d ld sp,hl defb 0f9h defb 056h defw l234bh defb 0cfh ;2162 inc rr defb 003h defb 041h defw l254bh defb 0cfh ;2167 dec rr defb 00bh defb 029h defw l254bh defb 0c7h ;216c inc r defb 004h defb 041h defw l24dfh defb 0c7h ;2171 dec r defb 005h defb 029h defw l24dfh defb 0ffh ;2176 ex af,af' defb 008h defb 034h defw l2357h defb 0cfh ;217b add hl,rr defb 009h defb 003h defw l235dh defb 0efh ;2180 ld (rr),a ;rr=bc,de defb 002h defb 056h defw l2366h defb 0efh ;2185 ld a,(rr) ;rr=bc,de defb 00ah defb 056h defw l236fh defb 000h ;218a EOT b_0x218B_start: ; 2 byte opdodes defb 0c7h ;218b ld r,nn defb 006h defb 056h defw l2384h defb 0ffh ;2190 add a,nn defb 0c6h defb 003h defw l237fh defb 0ffh ;2195 adc a,nn defb 0ceh defb 000h defw l237fh defb 0ffh ;219a sub a,nn defb 0d6h defb 0c9h defw l2397h defb 0ffh defb 0deh defb 0b7h defw l237fh defb 0ffh ;21a4 and a,nn defb 0e6h defb 006h defw l2397h defb 0ffh defb 0eeh defb 0cch defw l2397h defb 0ffh defb 0f6h defb 06ch defw l2397h defb 0ffh ;21b3 cp a,nn defb 0feh defb 013h defw l2397h defb 0ffh ;21b8 djnz defb 010h defb 02eh defw l23b0h defb 0ffh ;21bd jr defb 018h defb 054h defw l23b0h defb 0e7h ;21c2 jr,cc defb 020h defb 054h defw l23a1h defb 0ffh defb 0d3h ;21c8 out (nn),a defb 076h defw l23d5h defb 0ffh ;21cc in a,(nn) defb 0dbh defb 03fh defw l23c3h defb 000h ;21d1 EOT b_0x21D2_start: ; 3 byte opcodes defb 0c7h defb 0c2h defb 052h defw l23e0h defb 0c7h defb 0c4h defb 00ch defw l23e0h defb 0cfh defb 001h defb 056h defw l23fch defb 0ffh defb 0c3h defb 052h defw l23e6h defb 0ffh defb 0cdh defb 00ch defw l23e6h defb 0ffh defb 022h defb 056h defw l2404h defb 0ffh defb 02ah defb 056h defw l240dh defb 0ffh defb 032h defb 056h defw l2416h defb 0ffh defb 03ah defb 056h defw l2421h defb 000h b_0x2200_start: ; prefix ED + 1 byte opcode defb 044h ;2200 neg defb 066h defb 045h ;2202 retn defb 092h defb 04dh ;2204 reti defb 08eh defb 067h ;2206 rrd defb 0b1h defb 06fh ;2208 rld defb 0a2h defb 0a0h ;220a ldi defb 05fh defb 0a1h defb 01ch defb 0a2h defb 04bh defb 0a3h defb 07dh defb 0a8h ;2212 ldd defb 058h defb 0a9h defb 015h defb 0aah defb 044h defb 0abh defb 079h defb 0b0h ;221a ldir defb 062h defb 0b1h defb 01fh defb 0b2h defb 04eh defb 0b3h defb 072h defb 0b8h ;2222 lddr defb 05bh defb 0b9h defb 018h defb 0bah defb 047h defb 0bbh defb 06eh defb 08bh ;222a otdm defb 0d5h defb 09bh ;222c otdmr defb 0d9h defb 083h ;222e otim defb 0deh defb 093h ;2230 otimr defb 0e2h defb 076h ;2232 slp defb 0ebh defb 0ffh ;2234 EOT l2235h: defb 0e7h ;2235 in r,(c) ;r=bcde defb 040h defb 03fh defw l2455h defb 0f7h ;223a in r,(c) ;r=hl defb 060h defb 03fh defw l2455h defb 0ffh ;223f in r,(c) ;r=a defb 078h defb 03fh defw l2455h defb 0e7h defb 041h defb 076h defw l2461h defb 0f7h defb 061h defb 076h defw l2461h defb 0ffh ;224e out (c),r ;r=a defb 079h defb 076h defw l2461h defb 0cfh ;2253 sbc hl,rr defb 042h defb 0b7h defw l246dh defb 0cfh ;2258 adc hl,rr defb 04ah defb 000h defw l246dh defb 0ffh ;225d im 0 defb 046h defb 03dh defw l2427h defb 0ffh ;2262 im 1 defb 056h defb 03dh defw l242bh defb 0ffh ;2267 im 2 defb 05eh defb 03dh defw l242fh defb 0ffh ;226c ld i,a defb 047h defb 056h defw l2434h defb 0ffh defb 057h defb 056h defw l2439h defb 0ffh defb 04fh defb 056h defw l243eh defb 0ffh defb 05fh defb 056h defw l2443h defb 0cfh ;2280 mlt rr defb 04ch defb 0d2h defw l254bh defb 0c7h ;2285 tst r defb 004h defb 0eeh defw l24dfh defb 000h l228bh: defb 0e7h defb 000h defb 0cfh defw l230ch defb 0f7h defb 020h defb 0cfh defw l230ch defb 0ffh defb 038h defb 0cfh defw l230ch defb 0e7h defb 001h defb 0e7h defw l2315h defb 0f7h defb 021h defb 0e7h defw l2315h defb 0ffh defb 039h defb 0e7h defw l2315h defb 0ffh defb 064h defb 0eeh defw l2397h defb 0ffh defb 074h defb 0f1h defw l2397h defb 000h l22b4h: defb 0efh defb 043h defb 056h b_0x22B7_start: defw l2476h b_0x22B9_start: defb 0ffh defb 073h defb 056h b_0x22BC_start: defw l2476h b_0x22BE_start: defb 0efh defb 04bh defb 056h b_0x22C1_start: defw l247fh b_0x22C3_start: defb 0ffh defb 07bh defb 056h b_0x22C6_start: defw l247fh b_0x22C8_start: defb 000h l22c9h: defb 0f8h defb 000h defb 09bh b_0x22CC_start: defw l24aeh b_0x22CE_start: defb 0f8h defb 008h defb 0aah b_0x22D1_start: defw l24aeh b_0x22D3_start: defb 0f8h defb 010h defb 096h b_0x22D6_start: defw l24aeh b_0x22D8_start: defb 0f8h defb 018h defb 0a5h b_0x22DB_start: defw l24aeh b_0x22DD_start: defb 0f8h defb 020h defb 0c0h b_0x22E0_start: defw l24aeh b_0x22E2_start: defb 0f8h defb 028h defb 0c3h b_0x22E5_start: defw l24aeh b_0x22E7_start: defb 0f8h defb 038h defb 0c6h b_0x22EA_start: defw l24aeh b_0x22EC_start: defb 0c0h defb 040h defb 009h b_0x22EF_start: defw l2487h b_0x22F1_start: defb 0c0h defb 080h defb 088h b_0x22F4_start: defw l2487h b_0x22F6_start: defb 0c0h defb 0c0h defb 0bdh b_0x22F9_start: defw l2487h b_0x22FB_start: defb 000h l22fch: call l24dfh call sub_257ch jp l24ebh l2305h: call sub_2579h jp l24ebh l230bh: ret l230ch: call l24dfh call sub_257ch jp l23c6h l2315h: call l23c6h call sub_257ch jp l24dfh l231eh: comst ld a,(iy+000h) comend and 038h jp out.hex l232ah: ld hl,b_0x2333_start call PSTR jp l253eh b_0x2333_start: DC '(SP),' l2338h: ld a,'(' call OUTCHAR call l253eh ld a,')' jp OUTCHAR l2345h: ld hl,l1d86h jp PSTR l234bh: ld hl,b_0x2354_start call PSTR jp l253eh b_0x2354_start: DC 'SP,' l2357h: ld hl,b_0x1D80_start jp PSTR l235dh: call l253eh call sub_257ch jp l254bh l2366h: call sub_2372h call sub_257ch jp l23dbh l236fh: call sub_2579h sub_2372h: ld a,'(' call OUTCHAR call l254bh ld a,')' jp OUTCHAR l237fh: call sub_2579h jr l2397h l2384h: call l24dfh call sub_257ch ld a,(is.pfx.IXY) and a comst ld a,(iy+002h) comend jr nz,l239eh l2397h: comst ld a,(iy+001h) comend l239eh: jp out.hex l23a1h: comst ld a,(iy+000h) comend and 018h call sub_2568h call sub_257ch l23b0h: comst ld c,(iy+001h) comend ld a,c rla sbc a,a ld b,a push iy pop hl add hl,bc inc hl inc hl jr l23f0h l23c3h: call sub_2579h l23c6h: ld a,028h call OUTCHAR comst ld a,(iy+001h) comend jp l252bh l23d5h: call l23c6h call sub_257ch l23dbh: ld a,041h jp OUTCHAR l23e0h: call l2561h call sub_257ch l23e6h: comst ld l,(iy+001h) ld h,(iy+002h) comend l23f0h: ld a,002h sub_23f2h: ld (XBE03),a ld (XBE01),hl call out.hl ret l23fch: call l254bh call sub_257ch jr l23e6h l2404h: call sub_24c6h call sub_257ch jp l253eh l240dh: call l253eh call sub_257ch jp sub_24c6h l2416h: call sub_24c6h call sub_257ch ld a,041h jp OUTCHAR l2421h: call sub_2579h jp sub_24c6h l2427h: ld a,030h jr l2431h l242bh: ld a,031h jr l2431h l242fh: ld a,032h l2431h: jp OUTCHAR l2434h: ld hl,b_0x2449_start jr l2446h l2439h: ld hl,l244ch jr l2446h l243eh: ld hl,l244fh jr l2446h l2443h: ld hl,l2452h l2446h: jp PSTR b_0x2449_start: DC 'I,A' l244ch: DC 'A,I' l244fh: DC 'R,A' l2452h: DC 'A,R' l2455h: call l24dfh call sub_257ch ld hl,t__C_ jp PSTR l2461h: ld hl,t__C_ call PSTR call sub_257ch jp l24dfh l246dh: call l253eh call sub_257ch jp l254bh l2476h: call sub_24c6h call sub_257ch jp l254bh l247fh: call l254bh call sub_257ch jr sub_24c6h l2487h: ld a,(is.pfx.IXY) and a jr nz,l2496h comst ld a,(iy+001h) comend jr l249dh l2496h: comst ld a,(iy+002h) comend l249dh: push af rra rra rra and 007h add a,'0' call OUTCHAR call sub_257ch pop af jr l24f2h l24aeh: ld a,(is.pfx.IXY) and a jr nz,l24bdh comst ld a,(iy+001h) comend jr l24c4h l24bdh: comst ld a,(iy+002h) comend l24c4h: jr l24f2h sub_24c6h: ld a,'(' call OUTCHAR comst ld l,(iy+001h) ld h,(iy+002h) comend ld a,001h call sub_23f2h ld a,')' jp OUTCHAR l24dfh: comst ld a,(iy+000h) comend rra rra rra jr l24f2h l24ebh: comst ld a,(iy+000h) comend l24f2h: and 007h cp 006h jr nz,l2533h ld a,(is.pfx.IXY) and a ld a,006h jr z,l2533h ld hl,b_0x2538_start ld a,(is.pfx.IXY) dec a jr z,l250ch ld hl,b_0x253B_start l250ch: call PSTR comst ld a,(iy+001h) comend and a push af jp m,l2523h ld a,'+' call OUTCHAR pop af jr l252bh l2523h: ld a,'-' call OUTCHAR pop af neg l252bh: call out.hex ld a,')' jp OUTCHAR l2533h: ld hl,t_BCDEHL_HL_A jr l2572h b_0x2538_start: DC '(IX' b_0x253B_start: DC '(IY' l253eh: ld a,(is.pfx.IXY) ld hl,t_HL.IX.IY jr l2572h l2546h: ld hl,t_BC.DE.HL.AF jr l254eh l254bh: ld hl,t_BC.DE.HL.SP l254eh: comst ld a,(iy+000h) comend rra rra rra rra and 003h cp 002h jr z,l253eh jr l2572h l2561h: comst ld a,(iy+000h) comend sub_2568h: rra rra rra and 007h ld hl,t_tstfl_ZCPS jr l2572h l2572h: ld b,a call sub_0a48h jp PSTR sub_2579h: call l23dbh sub_257ch: ld a,',' jp OUTCHAR sub_2581h: call PSTR l2584h: call OUTBL inc c ld a,c cp 006h jr nz,l2584h ret 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' DB 0 t_BCDEHL_HL_A: DC 'B' DC 'C' DC 'D' DC 'E' DC 'H' DC 'L' DC '(HL)' DC 'A' DB 0 t_BC.DE.HL.SP: DC 'BC' DC 'DE' DC 'HL' DC 'SP' DB 0 t_BC.DE.HL.AF: DC 'BC' DC 'DE' t_HL.AF: DC 'HL' DC 'AF' DB 0 t_BC.DE.IY.SP: DC 'BC' DC 'DE' DC 'IY' DC 'SP' DB 0 t_BC.DE.IX.SP: DC 'BC' DC 'DE' DC 'IX' DC 'SP' DB 0 t_HL.IX.IY: DC 'HL' t_IX.IY: DC 'IX' DC 'IY' DB 0 t_tstfl_ZC: DC 'NZ' DC 'Z' DC 'NC' DC 'C' DC 'NE' DC 'EQ' DC 'GE' DC 'LT' DB 0 t_tstfl_ZCPS: DC 'NZ' DC 'Z' DC 'NC' DC 'C' DC 'PO' 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 sub_26e7h: ld hl,(REG.PC) ld a,h or l jr z,l2715h ld iy,(REG.PC) call sub_1f9eh jp nc,ERROR ld c,b ld b,000h ld hl,(REG.PC) add hl,bc call sub_1117h ld iy,(REG.PC) ld hl,b_0x2717_start call lookup_opc ccf ret c ex de,hl call CALL.HL call c,sub_1117h l2715h: scf ret b_0x2717_start: db 0ffh db 0ddh db 000h dw x278d db 0ffh db 0fdh db 000h dw x2792 db 0ffh db 0edh db 000h dw x27a2 l2726h: db 0ffh db 0cdh db 000h dw x275e db 0ffh db 0c3h db 000h dw x2769 db 0ffh db 0e9h db 000h dw x2788 db 0ffh db 0c9h db 000h dw x27c9 db 0ffh db 0cfh db 000h dw x280e db 0c7h db 0c7h db 000h dw x27ea db 0c7h db 0c4h db 000h dw x275e db 0f7h db 010h db 000h dw x2775 db 0e7h db 020h db 000h dw x2775 db 0c7h db 0c2h db 000h dw x2769 db 0c7h db 0c0h db 000h dw x27b3 db 000h x275e: ld a,(XBFE8) and a jr nz,x2769 ld a,(TCFLG) and a ret nz x2769: comst ld l,(iy+001h) ld h,(iy+002h) comend scf ret x2775: comst ld c,(iy+001h) comend ld a,c rla sbc a,a ld b,a ld hl,(REG.PC) add hl,bc inc hl inc hl scf ret x2788: ld hl,(REG.L) scf ret x278d: ld hl,(reg.ix) jr l2795h x2792: ld hl,(reg.iy) l2795h: comst ld a,(iy+001h) comend cp 0e9h scf ret z and a ret x27a2: comst ld a,(iy+001h) comend cp 04dh jr z,x27c9 cp 045h jr z,x27c9 and a ret x27b3: comst ld a,(iy+000h) comend ld (XBEDD),a ld hl,(REG.F) push hl pop af call XBEDD scf jr c,x27c9 ret x27c9: ld a,(XBFE8) and a jr nz,l27dah ld a,(TCFLG) and a jr z,l27dah call l27dah pop hl ret l27dah: ld hl,(REG.SP) comst ld e,(hl) inc hl ld d,(hl) comend ex de,hl call sub_1117h and a ret x27ea: ld a,(ddtzrst) comst cp (iy+000h) comend ret z comst ld a,(iy+000h) comend and 038h ld l,a ld h,000h ld a,(XBFE8) and a jr nz,l280ch ld a,(TCFLG) and a ret nz l280ch: scf ret x280e: and a ret CMD.C: ld hl,CMD.C ld a,001h jr l281bh CMD.T: xor a ld hl,CMD.T l281bh: ld (CMD_RPT),hl ld (TCFLG),a ld a,(de) sub 'N' jr nz,l2827h inc de l2827h: ld (TCNFLG),a ld a,(de) sub 'J' jr nz,l2830h inc de l2830h: ld (TRJFLG),a call sub_289fh jr z,l283eh ld hl,1 call get_lastarg_def l283eh: ld (TCCSTR),hl sub a ld (XA747),a l2845h: call sub_26e7h jr l289ch l284ah: call sub_0e68h ld a,(TRJFLG) and a jr nz,l2864h ld iy,(REG.PC) call sub_28c1h jr z,l2864h ld hl,l2726h call lookup_opc jr nc,l2845h l2864h: ld a,(XBFEA) and a jr z,l2881h ld de,(TCCSTR) call EXPR ld a,h or l add a,0ffh sbc a,a ld hl,XBFEA xor (hl) bit 1,a jr z,l288ch l287eh: jp l102eh l2881h: ld hl,(TCCSTR) dec hl ld (TCCSTR),hl ld a,h or l jr z,l287eh l288ch: call sub_26e7h jr nc,l287eh ld a,(TCNFLG) ld b,a ld a,(XA747) or b ld (XA747),a l289ch: jp l1183h sub_289fh: call SKIPBL xor a ld (XBFEA),a ld a,(de) cp 'U' jr z,l28aeh cp 'W' ret nz l28aeh: inc de push af push de call EXPR jp c,ERROR call assert_eol pop hl pop af ld (XBFEA),a sub a ret sub_28c1h: comst ld a,(iy+000h) ld b,(iy+0001) comend cp 0edh jr z,l28dbh and 0dfh cp 0ddh ret nz ld a,b cp 0e9h ret l28dbh: ld a,b and 0f7h cp 045h ret ?excom: ex (sp),hl push af push bc push de ld c,(hl) ld b,000h inc hl ld a,?lcmax sub c ld de,?exeit ldir ex de,hl ld (hl),018h inc hl ld (hl),a ex de,hl pop de pop bc pop af ex (sp),hl if CPU_Z180 push hl ld hl,(ubbr) else push af ld a,(ubnk) endif if ROMSYS push af ld a,(uromen) endif jp ?comcod ;------------------------------------------ ; ddtram ;------------------------------------------ vartab: ; dseg cseg ddtram: ;todo: ; The following 2 params are changeable by user. ; Should these moved to top ram? ; ddtzrst: rst DDTZRSTVEC ;rst used by ddtz ddtei: ei ;ints enabled/disabled while ddtz is running ret ; offs.pc: dw TPA offs.@: dw 0 CMD_ERR: dw 0 CMD_RPT: dw DDTZML ci.buf: db 80 rept 83 db 0 endm CON.COL: db 0 XA747: db 0 bp_tab: rept BP_CNT db 0,0 dw 0,0,0 endm BP_SIZE equ 8 sexp1: dw sexpbuf sexp2: dw sexpbuf sexpbuf: rept 128 db 0 endm sexpbufe: msg.Y: dc 'Y0' reg.Y: rept 10 dw 0 endm lst.S: dw 0 lst.IP: dw 0 lst.OP: dw 0 lst.OD: db 0 lst.Qj: db 0 lst.D: dw 0 HILOD: dw 0 MAXLOD: dw 0 XB068: dw 0 lst.A: dw 0 XB06C: dw 0 pfx.IXY: db 000h is.pfx.IXY: db 000h lst.L: dw 0 XBE01: dw 0 XBE03: db 000h XBEDD: ret ;ret cc and a pop hl inc hl jp (hl) XBFE8: db 0 TCFLG: db 0 XBFEA: db 0 TCCSTR: dw 0 TCNFLG: db 0 TRJFLG: db 0 wstrtflg: db 1 cseg vartabe: ;------------------------------------------ .phase sysram_start+bs$stack$size $stack: $stcka equ $ - bs$stack$size curphse defl $ .dephase sysramc: .phase curphse topcodbeg: reg.l2: db 0 ; 0fe50h reg.h2: db 0 ; 0fe51h reg.e2: db 0 ; 0fe52h reg.d2: db 0 ; 0fe53h reg.c2: db 0 ; 0fe54h reg.b2: db 0 ; 0fe55h reg.f2: db 0 ; 0fe56h reg.a2: db 0 ; 0fe57h db 0 reg.i: db high ivtab reg.iy: dw 0 ; 0fe5ah reg.ix: dw 0 ; 0fe5ch reg.e: db 0 ; 0fe5eh reg.d: db 0 ; 0fe5fh reg.c: db 0 ; 0fe60h reg.b: db 0 ; 0fe61h if ROMSYS udcntl: db CWAITIO ; 0fe62h (mem-, io- wait) uromen: db ROM_DIS ; 0fe63h endif if CPU_Z180 ubbr: db 0 ; 0fe64h ucbar: db USR$CBAR ; 0fe65h else db 0 ; 0fe64h ubnk: db 0 ; 0fe65h endif reg.f: db 0 ; 0fe66h reg.a: db 0 ; 0fe67h reg.l: db 0 ; 0fe68h reg.h: db 0 ; 0fe69h reg.sp: dw TOPRAM ; 0fe6ah $go: if ROMSYS out (000h),a ;064c fe6c out0 (dcntl),l pop hl endif if CPU_Z180 out0 (cbar),h out0 (bbr),l else ld a,h call selbnk endif pop af pop hl ld sp,(reg.sp) reg.iff: ei db 0C3h ;jp TPA ;065f feff ($+1): reg.pc reg.pc: dw TPA bpent: ld (reg.l),hl ;0662 fe82: bpent: pop hl dec hl ld (reg.pc),hl ld (reg.sp),sp ld sp,reg.l push af if CPU_Z180 ;;; TODO: cbar on trap? in0 h,(cbar) in0 l,(bbr) ld a,SYS$CBAR out0 (cbar),a else ld a,(@cbnk) ld h,a xor a ld l,a call selbnk endif push hl if ROMSYS in0 l,(dcntl) ld a,CWAITROM+CWAITIO out0 (dcntl),a ld a,($crom) cp c$rom ld a,ROM_EN out (000h),a endif jp bpddtz ?comcod: if ROMSYS out (000h),a ;0692 feb2 pop af endif if CPU_Z180 out0 (cbar),h out0 (bbr),l pop hl else call selbnk pop af endif ?exeit: ds ?lcmax+2 push af if CPU_Z180 ld a,SYS$CBAR out0 (cbar),a ;;; TODO: bbr? else xor a call selbnk endif if ROMSYS ld a,ROM_EN out (000h),a endif pop af ret topcodend: curph defl $ .dephase sysrame: end