; Disassembled ddtz.com, version "DDT/Z [8101]" ; with modified relocater. ; ; Build steps: ; - Assemble to a .REL file with M80 or a compatible assembler. ; - 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. maclib config.inc ; Some greneral definitions BS equ 08h TAB equ 09h CR equ 0dh LF equ 0ah DEL equ 7fh CNTRX equ 'X'-'@' ; CP/M memory layout BDOS equ 5 TPA equ 0100h ; ddtz specific definitions STACK_SIZE equ 80 ;ddtz internal stack CONBUF_SIZE equ 80 ;Size of console input buffer BP_CNT equ 12 ;Number of breakpoints BP_SIZE equ 4 ;Size of a breakpoint record bitmap_size equ (prog_size+7)/8 ;------------------------------------------------------------------------------- cseg start: ddtz_base: jr reloc if CPM nop else iobyte db 1 endif l0003h: rst 30h ;rst used by ddtz di_or_ei: ;ints enabled/disabled while ddtz is running nop ret ;------------------------------------------------------------------------------- signon: db 'DDTZ/180' db ' - Version ' maclib version.inc defvers dc ' (' ;------------------------------------------------------------------------------- reloc_getbit macro local nextbit exx djnz nextbit ld b,8 ;reload bit counter ld e,(hl) ;get next 8 relocation bits inc hl nextbit: sla e exx endm ;------------------------------------------------------------------------------- ; Clear old position cmde_clr: ld (hl),0 inc hl dec bc ld a,b or c jr nz,cmde_clr ; Determine current position reloc: ld a,i ;get iff2 ex af,af' di ld sp,028h-2 ;rst instr needs a minimal stack pop bc ;save 026h,027h pop de ;save 028h,029h ld hl,0e9e1h ;opcpdes pop hl/jp (hl) push hl rst 028h wearehere: ld (028h-2),bc ld (028h),de ld de,-(wearehere-ddtz_base) add hl,de ; hl: ld de,ddtz_base ; de: or a sbc hl,de ex de,hl ; de: reloc offset ld hl,stack add hl,de ld sp,hl ex af,af' push af pop bc bit 2,c jr z,$+3 ei ld hl,ddtz_end ;start of reloc bitmap add hl,de push hl exx pop hl ld b,1 ;init bit counter b exx LD HL,ddtz_base add hl,de ;--> ddtz_base reloc_lp: push de push hl ld de,4 ld a,2 ld hl,0 reloc_l: reloc_getbit jr nc,reloc_got cp 16 jr z,reloc_done add hl,de ld b,a ex de,hl reloc_l1: add hl,hl djnz reloc_l1 ex de,hl add a,a jr reloc_l reloc_got: ex de,hl ld hl,0 ld b,a reloc_bitloop: reloc_getbit adc hl,hl djnz reloc_bitloop add hl,de pop de add hl,de pop de LD A,(HL) ADD A,E LD (HL),A INC HL LD A,(HL) ADC A,D LD (HL),A inc hl jr reloc_lp reloc_done: exx ld (bitmap_end),hl ;------------------------------------------------------------------------------- init: LD SP,stack if CPM ld hl,(1) ;wboot addr ld de,convec ex de,hl ld b,3 vini_l: inc de inc de inc de inc hl ld (hl),e inc hl ld (hl),d inc hl djnz vini_l else xor a dec a daa ; Z80: 099H, x180+: 0F9H cp 99h ; Result on 180 type cpus is F9 here. Thanks Hitachi ;;; jr z,ini_z80 ;; call cinit jr ini_sign ini_z80: ; if ... ; .printx Error: Not yet implemented! ; db "Stop ; endif endif ; CPM ini_sign: ld hl,signon call pstr ld hl,ddtz_base call out_hl call pstr_inl dc ' - ' ld hl,(bitmap_end) dec hl call out_hl call pstr_inl dc ')',CR,LF ld a,i ld (reg.i),a ld a,0f3h jp po,l0093h ld a,0fbh l0093h: ld (reg.iff),a call di_or_ei ld hl,ddtz_base ld l,000h ld (reg_sp),hl jp mainloop ;------------------------------------------------------------------------------- if CPM convec: const: jp 0 ; return console input status conin: jp 0 ; return console input character conout: jp 0 ; send console output character else include z84c015.inc max_device equ 2 ;------------------------------------------------------------------------------- ; init device cinit: ; a = device call vector_io_0 dw sio0init dw sio1init ; character input status const: ; return a != 0 if character waiting call vector_io dw sio0ista dw sio1ista ; character input conin: ; return a = input char call vector_io dw sio0inp dw sio1inp ; character output conout: ; c = output char call vector_io dw sio0out dw sio1out ;------------------------------------------------------------------------------- vector_io: ld a,(iobyte) ld hl,iobyte_cur cp (hl) jr z,vector_io_0 ld (hl),a push af call cinit pop af vector_io_0: pop hl cp max_device jr c,exist ld a,max_device ; use null device if a >= max$device exist: call add_hl_a2 ld a,(hl) inc hl ld h,(hl) ld l,a jp (hl) ;------------------------------------------------------------------------------- ; ; TC = CLK / SIO_CLK / Baud ; TC = 3072000 / 16 / 19200 = 10 initab0: db 2 ;Nr of bytes db CTC_CH2 db 01000111b ;Counter Mode, TC follows, Reset db 10 db 9 ;Nr of bytes db SIOACtrl db R0+CHRST ;Reset SIO db R4+RESI db CLK16+STOP2 ; db R3 db RXB8+RXEN ; db R5 db TX8B+TXEN db R1+RESI db 0 db 0 initab1: db 2 ;Nr of bytes db CTC_CH3 db 01000111b ;Counter Mode, TC follows, Reset db 10 db 9 ;Nr of bytes db SIOBCtrl db R0+CHRST ;Reset SIO db R4+RESI db CLK16+STOP2 ; db R3 db RXB8+RXEN ; db R5 db TX8B+TXEN db R1+RESI db 0 db 0 ;------------------------------------------------------------------------------- sio0init: ld hl,initab0 jr ioinil sio1init: ld hl,initab1 ;fall thru ;------------------------------------------------------------------------------- ioinil: push bc jr ioi_nxt ioi_l: ld c,(hl) ;port address inc hl otir ioi_nxt: ld b,(hl) ;count inc hl inc b djnz ioi_l pop bc ret ;------------------------------------------------------------------------------- sio0ista: in a,(SIOACtrl) rrca sbc a,a ret sio1ista: in a,(SIOBCtrl) rrca sbc a,a ret sio0inp: in a,(SIOACtrl) rrca jr nc,sio0inp in a,(SIOAData) ret sio1inp: in a,(SIOBCtrl) rrca jr nc,sio1inp in a,(SIOBData) ret sio0out: in a,(SIOACtrl) bit TXE,a jr z,sio0out ld a,c out (SIOAData),a ret sio1out: in a,(SIOBCtrl) bit TXE,a jr z,sio1out ld a,c out (SIOBData),a ret endif ; CPM ;------------------------------------------------------------------------------- CMDTAB: ; dw ERROR ;cmd_@ ;examine/substitute the displacement register @ ; dw ERROR ;cmd_A ;Assemble dw cmd_B ;Breakpoints display/set/clear dw ERROR ;cmd_C ;trace over Calls dw cmd_D ;Display memory in hex and ascii dw cmd_E ;rElocate debugger dw ERROR ;cmd_F ;specify Filename and command line dw cmd_G ;Go dw cmd_H ;compute Hex and other expressions dw cmd_I ;Input a byte from port dw ERROR ; dw ERROR ; dw cmd_L ;List disassembled code dw cmd_M ;Move memory [and verify] dw ERROR ; dw cmd_O ;Output a byte to port dw ERROR ; dw cmd_Q ;Qery memory for byte string dw cmd_R ;Read binary or hex file dw cmd_S ;Substitute memory dw cmd_T ;Trace dw ERROR ; dw cmd_V ;Verify (compare) two memory areas dw ERROR ;cmd_W ;Write a file to disk dw cmd_X ;eXamine [and substitute] registers dw ERROR ;cmd_Y ;examine [and substitute] Y variables dw cmd_Z ;Zap (fill) memory with a byte string ERROR: call pstr_inl dc '?',CR,LF ;fall thru mainloop: ld sp,stack ld hl,(reg.pc) call bp_clr_temporary ld hl,(cmd_rpt) ld de,mainloop push de call cp_hl_de ld a,'>' call outchar call nz,outchar call z,outbl call get_line call skipbl jr z,exe_hl pop hl push hl ld (cmd_rpt),hl inc de sub 'B' jr c,ERROR cp 'Z'+1-'B' jr nc,ERROR ld hl,CMDTAB call add_hl_a2 ld a,(hl) inc hl ld h,(hl) ld l,a exe_hl: CALL_HL: jp (hl) ;------------------------------------------------------------------------------- crlf: call pstr_inl dc CR,LF call inchar jr c,mainloop ret sub_01d9h: call pstr_inl dc '-' jp neg.hl out_hl_dec_neg: push hl call sub_01d9h defb 03eh ;ld a,.. swallow push hl out.hl.dec: push hl ld b,006h call sub_01f9h pop hl call pstr_inl dc '.' l01f3h: call outbl djnz l01f3h ret sub_01f9h: dec b push de ld de,10 call div_hl_de ld a,h or l call nz,sub_01f9h ld a,e pop de jr out_dgt out_hl_neg: push hl call sub_01d9h 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_dgt pop af out_dgt: or 0f0h daa add a,0a0h adc a,040h jr outchar out.bin.w: ld a,h call out.bin.b ld a,l out.bin.b: ld b,8 l01c9h: rlca push af and 1 call out_dgt pop af djnz l01c9h ld a,'"' jr outchar out.ascii: push bc ld c,a res 7,a cp ' ' push af call nc,outbl call pstr_inl dc '''' pop af jr nc,l0242h sub 0c0h ld b,a call pstr_inl dc '^' ld a,b l0242h: call outchar cp '''' call z,outchar call pstr_inl dc '''' sla c pop bc ret nc ld a,'.' jr outchar out_hl_bl2: call out_hl jr outbl2 out_hex_bl: call out_hex jr outbl outbl6: call outbl2 outbl4: call outbl2 outbl2: call outbl outbl: ld a,' ' outchar: push ix push iy push hl push de push bc push af and 07fh ld c,a call conout pop af pop bc pop de pop hl pop iy pop ix ret ;------------------------------------------------------------------------------- incharw: call inchar jr nc,incharw ret ;------------------------------------------------------------------------------- inchar: push ix push hl push de push bc call const and a jr z,inch1 call conin scf inch1: pop bc pop de pop hl pop ix ret ;------------------------------------------------------------------------------- DELC: ld a,b or a ret z call DELC1 dec hl dec b ld a,(hl) cp ' ' ret nc DELC1: call pstr_inl dc BS,' ',BS ret DELL: ld a,b ; or a ; ret z ; call DELC ; jr DELL ; ;------------------------------------------------------------------------------- get_line: push hl ; ld hl,conbuf ; ld b,0 ; inlnxtch: ld a,b ; cp CONBUF_SIZE ; jr z,inl_e ; call incharw ; cp CR ; jr z,inl_e ;Accept line cp LF ; jr z,inl_e ;Accept line cp BS ; jr z,gl_1 ; cp DEL ; jr nz,gl_2 ; gl_1: call DELC ;Delete Char jr inlnxtch ; gl_2: cp CNTRX ; jr nz,gl_3 ; call DELL ;Delete Line jr inlnxtch ; gl_3: cp TAB ; jr nz,gl_4 ; ld a,' ' ; gl_4: ld (hl),a ; cp ' ' ; jr nc,gl_5 ; ld a,'^' ;Controll characters call outchar ; ld a,(hl) ; add a,'@' ; gl_5: call outchar ; inc hl ; inc b ; jr inlnxtch ; inl_e: ld (hl),0 call CRLF ; ld de,conbuf ; pop hl ; ret ; ;------------------------------------------------------------------------------- get_char_upper: ld a,(de) toupper: cp 'a' ret c cp 'z'+1 ccf ret c and 05fh ret ;------------------------------------------------------------------------------- skipbl0: inc de skipbl: call get_char_upper cp ' ' jr z,skipbl0 or a ret ;------------------------------------------------------------------------------- next_arg: call skipbl cp ',' ret nz call skipbl0 cp a ret assert_eol: call skipbl ret z to_error: jp ERROR ;------------------------------------------------------------------------------- chk_stack: push hl push de ld hl,0 add hl,sp ld de,stack-(STACK_SIZE-28) call cp_hl_de pop de pop hl jr c,to_error ret ;------------------------------------------------------------------------------- add_hl_a2: add a,a add_hl_a: add a,l ld l,a ret nc inc h ret cp_hl_de: and a sbc hl,de add hl,de ret ;------------------------------------------------------------------------------- lookupch: ld b,0 l02f5h: ld a,(hl) and a ret z call get_char_upper cp (hl) jr z,l0300h inc hl inc b jr l02f5h l0300h: scf inc de ret sub_0303h: ld hl,t_reg_names ld b,07fh l030ch: inc b ld a,(hl) and a ret z call sub_031ch jr nc,l030ch res 7,b ret sub_031ch: push bc push de l031eh: call get_char_upper xor (hl) and 07fh jr nz,l0336h bit 7,(hl) inc hl inc de jr z,l031eh scf bit 7,b call z,sub_060ch jr nc,l0339h pop af scf pop bc ret l0336h: call str_sel_next l0339h: pop de and a pop bc ret str_sel: inc b jr str_sel2 str_sel1: call str_sel_next str_sel2: djnz str_sel1 ret str_sel_next: ld a,(hl) and a ret z l0348h: ld a,(hl) inc hl and a ret m jr l0348h get_arg_range_target: call get_arg_range push hl push bc call next_arg call get_arg_final ex de,hl pop bc pop hl ret sub_035dh: call expr jr c,error0 ret get_arg_final: call sub_035dh l0366h: jp assert_eol get_lastarg_def: call get_arg_def jr l0366h get_arg_def: push hl call expr jr c,l0375h ex (sp),hl l0375h: pop hl ret sub_0377h: call b_037c_start jr l0366h b_037c_start: defb 0e6h ;and a,.. clear carry get_arg_range: scf ex af,af' push bc push hl call expr jr nc,l038ch ex af,af' jr c,error0 ex af,af' pop hl defb 03eh ;ld a,.. swallow pop af l038ch: pop af call get_range jr nc,l0398h ex af,af' pop bc ret nc error0: jp ERROR l0398h: pop af ret get_range: call next_arg cp 'S' jr nz,l03a2h inc de l03a2h: push hl push af ;'S' flag call expr jr c,l03b8h ld b,h ld c,l pop af pop hl jr z,l03b6h ;'S'? ld a,c sub l ld c,a ld a,b sbc a,h ld b,a inc bc l03b6h: and a ret l03b8h: pop af pop hl jr z,error0 ;'S', but no expression following scf ret ;------------------------------------------------------------------------------- expr: call skipbl expr1: call do_factor ret c l0433h: call do_binary_op push hl push bc call do_factor pop bc ex de,hl ex (sp),hl jr nc,l0447h pop de ld a,b or c ret z jp ERROR l0447h: ld a,b or c push bc ret nz pop bc doop_add: add hl,de l044dh: pop de jr l0433h doop_sub: and a sbc hl,de jr l044dh doop_mlt: push bc ld b,h ld c,l ld hl,0 ld a,010h l045dh: add hl,hl ex de,hl add hl,hl ex de,hl jr nc,l0464h add hl,bc l0464h: dec a jr nz,l045dh pop bc jr l044dh doop_div: call div_hl_de jr l044dh doop_mod: call div_hl_de ex de,hl jr l044dh ; 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 ld b,h ;bc: y ld c,l ld hl,0 ;hl: r ld a,16 ; de: x (x shifted out, q shifted in) ; bc: y ; hl: r (initially 0) div_lp: ex de,hl add hl,hl ;x <<= 1 ex de,hl adc hl,hl ;r <<= 1 inc de or a sbc hl,bc jr nc,div_norestore dec de add hl,bc div_norestore: dec a jr nz,div_lp ex de,hl pop bc ret doop_and: ld a,h and d ld h,a ld a,l and e ld l,a jr l044dh doop_or: ld a,h or d ld h,a ld a,l or e ld l,a jr l044dh doop_xor: ld a,h xor d ld h,a ld a,l xor e ld l,a jr l044dh do_binary_op: push hl ld hl,tab_op_a call lookupch ld a,b ld hl,tblf_opa call add_hl_a2 ld c,(hl) inc hl ld b,(hl) pop hl ret tab_op_a: DB '+-*/%&!#',0 tblf_opa: dw doop_add dw doop_sub dw doop_mlt dw doop_div dw doop_mod dw doop_and dw doop_or dw doop_xor dw 0 ;------------------------------------------------------------------------------- fact_factor: call do_factor ret nc jp ERROR do_factor: call chk_stack call get.number ret nc inc de ld hl,ddtz_base-1 cp 'T' ret z ld hl,(high_load) cp 'H' ret z ld hl,(max_load) cp 'M' ret z ld hl,TPA cp 'L' ret z ld hl,(reg.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 '(' jr z,fact_mem cp '[' jr z,expr_brckt cp '''' jr z,fact_factstring dec de scf ret ;------------------------------------------------------------------------------- fact_factstring: ld hl,0 l054bh: ld a,(de) cp '''' jr z,l0557h and a ret z l0552h: ld h,l ld l,a inc de jr l054bh l0557h: inc de ld a,(de) cp '''' jr z,l0552h sub '.' or a ret nz inc de set 7,l ret fact_reg.CPU: call sub_0caeh jr nc,error1 ld a,(hl) inc hl ld h,(hl) ld l,a xor a ;clr cy, a=0 bit 0,c ret nz ld h,a ret fact_factinv: call fact_factor jr cpl.hl fact_factneg: call fact_factor neg.hl: dec hl cpl.hl: ld a,h cpl ld h,a ld a,l cpl ld l,a ret fact_mem: call expr1 jr c,error1 ld a,(de) cp ')' jr nz,error1 inc de ld a,(hl) inc hl ld h,(hl) 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,error1 ld a,(de) cp ']' inc de ret z error1: jp ERROR ;------------------------------------------------------------------------------- get.number: call get.hexdigit ret c push de test_number: inc de call get.hexdigit jr nc,test_number pop de cp '.' jr z,get_dec_number cp '"' jr z,get_bin_number ld hl,0 next_hexdigit: call get.hexdigit jr c,hexnum_done add hl,hl add hl,hl add hl,hl add hl,hl call add_hl_a inc de jr next_hexdigit hexnum_done: xor 'H' ret nz inc de ret get_bin_number: ld hl,0 next_bindigit: call get.bindigit l05dbh: inc de jr c,l05e4h add hl,hl call add_hl_a jr next_bindigit l05e4h: cp '"' jr nz,error11 call get.bindigit jr nc,l05dbh or a ret get_dec_number: ld hl,0 next_decdigit: call get.decdigit inc de jr c,decnum_done push bc add hl,hl ld b,h ld c,l add hl,hl add hl,hl add hl,bc pop bc call add_hl_a jr next_decdigit decnum_done: cp '.' ret z error11: jp ERROR sub_060ch: call get_char_upper cp 'Z'+1 jr l0614h get.hexdigit: ld a,(de) hex_digit: call toupper cp 'F'+1 l0614h: ccf ret c cp 'A' jr c,l061eh sub 'A'-10 ret get.decdigit: call get_char_upper l061eh: cp '9'+1 jr l0625h get.bindigit: call get_char_upper cp '1'+1 l0625h: ccf ret c cp '0' ret c sub '0' ret ;------------------------------------------------------------------------------- p_cpustat0: call assert_eol p_cpustat: call p_f call outbl2 ld hl,b_06e9_start ld de,b_0709_start ld b,6 l063eh: call p_regs djnz l063eh call outbl6 push hl push de ld de,(reg.pc) or a call p_disas_instr pop de pop hl call p_f2 call outbl2 ld b,7 l065bh: call p_regs djnz l065bh jp crlf p_f: ld a,(reg.f) call p_flags ld a,(reg.iff) cp 0f3h jr z,outbl_1 ld a,'E' jp outchar p_f2: ld a,(reg.f2) call p_flags jr outbl_1 p_flags: push hl ld hl,t_flag_names+7 ld c,a ld b,8 fl_loop: ld a,' ' cp (hl) ld a,c rlca ld c,a jr z,fl_skip ld a,(hl) call c,outchar call nc,outbl fl_skip: dec hl djnz fl_loop pop hl ret p_regs: push de call pstr call pstr_inl dc '=' ex (sp),hl ld e,(hl) inc hl ld d,(hl) inc hl ld a,(hl) inc hl push hl and a jr z,l06deh ex de,hl ld e,(hl) inc hl ld d,(hl) ex de,hl call out_hl jr l06e2h l06deh: ld a,(de) call out_hex l06e2h: pop de pop hl outbl_1: jp outbl b_06e9_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_0709_start: dw reg.a db 000h dw reg.c db 001h dw reg.e db 001h dw reg.l db 001h dw reg_sp db 001h dw reg.pc db 002h dw reg.a2 db 000h dw reg.c2 db 001h dw reg.e2 db 001h dw reg.l2 db 001h dw reg.ix db 001h dw reg.iy db 001h dw reg.i db 000h db 000h ;------------------------------------------------------------------------------- ; > E addr ; relocate debugger to addr ; > ER addr ; relocate just below addr ; ; Move debugger to given address and restart. ; New location must not overlap with current location. cmd_E: call skipbl sub 'R' jr nz,$+3 inc de push af call get_arg_final ex de,hl ld hl,(bitmap_end) ld bc,ddtz_base or a sbc hl,bc ld b,h ld c,l ex de,hl pop af jr nz,cmde_bottom sbc hl,bc cmde_bottom: ld ix,cmde_clr-ddtz_base ex de,hl ;de = dst add ix,de ld hl,ddtz_base ;hl = src push hl or a sbc hl,de call c,neg.hl ;abs(distance) or a sbc hl,bc jp c,error pop hl push hl push bc ldir pop bc pop hl jp (ix) ;------------------------------------------------------------------------------- ; > G [startaddr] [;breakp..] ; Go [to start] [with temporary breakpoints] cmd_G: call expr jr c,l0740h ld (reg.pc),hl l0740h: call skipbl jr z,user_go0 cp ';' jp nz,ERROR inc de ld a,002h call bp_enter user_go0: jp user_go ;------------------------------------------------------------------------------- bpl_init: ld b,BP_CNT ld ix,bp_tab ex (sp),hl ld (pbl_loop_adr),hl ex (sp),hl ret bpl_next: ld de,BP_SIZE push af add ix,de pop af dec b ret z ex (sp),hl ld hl,(pbl_loop_adr) ex (sp),hl ret bp_clr_temporary: call bpl_init ld a,(ix+000h) and 0f1h ld (ix+000h),a call bpl_next ret ;------------------------------------------------------------------------------- ; > B ; display all breakpoints ; > B breakp [breakp..] ; set breakpoints ; > BX ; clear all breakpoints ; > BX breakp [breakp..] ; clear breakpoints ; ; breakp can be any valid expression cmd_B: call skipbl jr z,bp_print inc de cp 'X' jr z,bp_clr0 dec de ld a,001h jp bp_enter bp_clr0: call skipbl jr z,bp_clr_all bp_clr_next: call expr jp c,assert_eol push de call bp_clr pop de call next_arg jr bp_clr_next bp_clr_all: scf bp_clr: call bpl_init push af jr c,l07a7h ld e,(ix+002h) ld d,(ix+003h) call cp_hl_de jr nz,l07aeh l07a7h: ld (ix+000h),000h l07aeh: pop af call bpl_next ret bp_print: ld c,0 call bpl_init bit 0,(ix+000h) jr z,bp_pr_cont ld l,(ix+002h) ld h,(ix+003h) call out_hl_bl2 inc c bp_pr_cont: call bpl_next ld a,c or a call nz,crlf ret ;------------------------------------------------------------------------------- ; Add break points to list ; A = 1 Permanent (B command) ; A = 2 Temporary (G command) bp_enter: ld b,a call skipbl ret z push bc call expr jr c,error12 pop bc bit 0,b push bc push de push hl call nz,bp_clr pop hl call bp_get_freeslot pop de ld (ix+002h),l ld (ix+003h),h call next_arg pop af ld (ix+000h),a and 00fh jr bp_enter bp_get_freeslot: call bpl_init ld a,(ix+000h) and 00fh ret z call bpl_next error12 jp ERROR ;------------------------------------------------------------------------------- ; Breakpoint handling routine. bpddtz: ld (reg.l),hl pop hl dec hl ld (reg.pc),hl ld (reg_sp),sp ld sp,reg.l push de push bc push af push ix push iy ld a,i call di_or_ei ld h,a ld l,000h push hl ld a,0f3h ; EI jp po,l08dfh ld a,0fbh ; DI l08dfh: ld (reg.iff),a ex af,af' push af exx push bc push de push hl call bp_restore_mem ld a,(b_21e2_start) dec a jr z,l090bh call inchar ;Keyboard hit? jr c,do_break ;yes call sub_0913h and a jp z,user_go and 083h jp z,l2151h do_break: call bp_clr_temporary call p_cpustat jp mainloop l090bh: ld (b_21e2_start),a ld c,007h jp l0a41h sub_0913h: ld a,080h ex af,af' call bpl_init ld a,(ix+000h) and 007h jr z,l0938h ld e,(ix+002h) ld d,(ix+003h) ld hl,(reg.pc) call cp_hl_de jr nz,l0938h ex af,af' res 7,a or (ix+000h) ex af,af' l0938h: call bpl_next ex af,af' ret bp_restore_mem: call bpl_init bit 5,(ix+000h) res 5,(ix+000h) jr z,l099ah ld l,(ix+002h) ld h,(ix+003h) ld a,(l0003h) cp (hl) jr nz,l099ah ld a,(ix+001h) ld (hl),a l099ah: res 3,(ix+000h) call bpl_next ret bp_tst_@pc: call bpl_init ld a,(ix+000h) and 003h ;User bp (temporary or permanent)? jr z,bp_tst_e ;No, check next ld e,(ix+002h) ld d,(ix+003h) ld hl,(reg.pc) call cp_hl_de ;Current PC is on a User bp ret z ;Return zero bp_tst_e: call bpl_next sub a inc a ;Not on a user bp ret ;Return not zero bp_trace_enter: call bp_get_freeslot ld (ix+002h),l ld (ix+003h),h ld a,(b_21e2_start) and a ld a,008h jr nz,bp_t_e rra bp_t_e: ld (ix+000h),a ret bp_set_to_mem: call bpl_init ld a,(ix+000h) and c jr z,l0a1dh set 5,(ix+000h) ld l,(ix+002h) ld h,(ix+003h) ld a,(hl) ld (ix+001h),a ld a,(l0003h) ld (hl),a and 038h ld h,000h ld l,a ld (hl),0c3h inc hl ld de,bpddtz ld (hl),e inc hl ld (hl),d l0a1dh: call bpl_next ret ;------------------------------------------------------------------------------- user_go: sub a ld (b_21e2_start),a call bp_tst_@pc ld c,007h jr nz,l0a41h ld a,001h ld (b_21e2_start),a call tc_set_bp ld c,008h l0a41h: call bp_set_to_mem ld sp,reg.l2 pop hl pop de pop bc pop af exx ex af,af' pop af ld i,a pop iy pop ix pop af pop bc pop de pop hl ld sp,(reg_sp) jp reg.iff ;------------------------------------------------------------------------------- ; > Y ; examine all Y variables ; > Y[0..9] ; examine (and substitute) an Y variable ;------------------------------------------------------------------------------- ; > X ; eXamine (display) all cpu registers and ; the instruction at the current program counter ; > X register ; eXamine (and substitute) a register cmd_X: call skipbl call sub_0caeh jp nc,p_cpustat0 call assert_eol ld a,b cp 25 jr z,l0c5fh cp 26 jr z,l0c4fh ex de,hl ld hl,t_reg_names call pstr_sel call l0c33h call outbl push de push bc call get_line call skipbl jr z,l0c30h call get_arg_final ex de,hl pop bc pop hl ld (hl),e bit 0,c ret z inc hl ld (hl),d ret l0c30h: pop af pop hl ret l0c33h: call pstr_inl dc '=' ld a,(de) bit 0,c jp z,out_hex ld l,a inc de ld a,(de) dec de ld h,a jp out_hl l0c4fh: call p_f ld a,0f3h ld (reg.iff),a scf call sub_0c6ah ld (reg.f),a ret l0c5fh: call p_f2 and a call sub_0c6ah ld (reg.f2),a ret sub_0c6ah: push af call outbl call assert_eol call get_line pop af ex af,af' ld b,0 l0c76h: call skipbl ld a,b ret z push bc ld hl,t_flag_names call lookupch jp nc,ERROR inc b xor a scf nxt_f: rla djnz nxt_f pop bc jr c,l0c97h or b ld b,a jr l0c76h l0c97h: ex af,af' jp nc,ERROR ex af,af' ld a,0fbh ld (reg.iff),a jr l0c76h t_flag_names: db 'CNV H ZSE',0 sub_0caeh: call sub_0303h ret nc ld a,b add a,b add a,b ld hl,b_0cfa_start call add_hl_a ld c,(hl) inc hl ld a,(hl) inc hl ld h,(hl) ld l,a scf ret t_reg_names: 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: db 003h dw reg.c2 db 003h dw reg.e2 db 003h dw reg.l2 db 003h dw reg.c db 003h dw reg.e db 003h dw reg.l db 000h dw reg.a2 db 000h dw reg.b2 db 000h dw reg.c2 db 000h dw reg.d2 db 000h dw reg.e2 db 000h dw reg.h2 db 000h dw reg.l2 db 000h dw reg.a db 000h dw reg.b db 000h dw reg.c db 000h dw reg.d db 000h dw reg.e db 000h dw reg.h db 000h dw reg.l 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 000h dw reg.f2 db 000h dw reg.f ;------------------------------------------------------------------------------- ; > S [startaddr] ; Substitute memory cmd_S: ld hl,(last_S) call get_lastarg_def l0d60h: ld (last_S),hl call out_hl call outbl ld a,(hl) call out_hex call outbl2 call get_line call skipbl inc hl jr z,l0d60h dec hl inc de cp '.' jr nz,cmds_dash call get_char_upper or a jr nz,l0d8ah ret cmds_dash: jp z,assert_eol cp '-' jr nz,l0d8ah call get_char_upper or a dec hl jr z,l0d60h inc hl l0d8ah: dec de call sub_0ef8h jr l0d60h ;------------------------------------------------------------------------------- ; > @ ; examine (substitute) displacement register @ ;cmd_@: ;------------------------------------------------------------------------------- ; >>I [port] ; Input a byte from port cmd_I: ld (cmd_rpt),hl ld hl,(last_I) call get_lastarg_def ld (last_I),hl ld b,h ld c,l in a,(c) push af call out_hex call outbl4 pop af call out.bin.b jp crlf ;------------------------------------------------------------------------------- ; >>O [byte] [port] ; Output a byte to a port cmd_O: ld (cmd_rpt),hl ld hl,(last_O_val) call get_arg_def ld a,l ld (last_O_val),a push af call next_arg ld hl,(last_O_addr) call get_lastarg_def ld (last_O_addr),hl ld b,h ld c,l pop af out (c),a ret ;------------------------------------------------------------------------------- ; > V startaddr endaddr targetaddr ; Verify (compare) two memory areas cmd_V: call get_arg_range_target l0dedh: push bc ld a,(de) ld b,(hl) cp b jr z,l0e10h ld c,a call out_hl call outbl ld a,b call out_hex call outbl2 ld a,c call out_hex_bl ex de,hl call out_hl ex de,hl call crlf l0e10h: pop bc inc de cpi jp pe,l0dedh ret ;------------------------------------------------------------------------------- ; > M startaddr endaddr destaddr ; Move memory cmd_M: call get_arg_range_target call cp_hl_de jr nc,cmdm_up add hl,bc ex de,hl add hl,bc ex de,hl dec hl dec de lddr ret cmdm_up: ldir ret ;------------------------------------------------------------------------------- ; > H ; display Highest load address of last filed loaded, Maximum "High" ; off all loaded files, and Top address of available memory ; > H expression ; evaluate expression and display result in hex, decimal and other formats cmd_H: call expr jp c,p_max_high0 call assert_eol call out_hl_bl2 call out_hl_neg call outbl4 call out.hl.dec call outbl2 call out_hl_dec_neg call outbl4 call out.bin.w call outbl2 ld a,l call out.ascii jp crlf ;------------------------------------------------------------------------------- ; > Q[J] startaddr endaddr bytes ; Query memory for a byte string [Justified] cmd_Q: call get_arg_range push bc push hl call sub_0ee6h pop hl l0e96h: 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 ld bc,16 and a ;clear carry call sub_0f58h pop bc l0eb0h: inc hl ex (sp),hl dec hl ld a,h or l ex (sp),hl jr nz,l0e96h pop bc ret ;------------------------------------------------------------------------------- ; > Z startaddr endaddr bytes ; Zap (fill) memory with a byte string cmd_Z: call get_arg_range push bc push hl call sub_0ee6h ld a,b pop hl pop bc push hl ex de,hl l0ec7h: ldi jp po,l0ed3h dec a jr nz,l0ec7h pop hl ldir ret l0ed3h: pop hl ret sub_0ee6h: ld hl,conbuf call sub_0ef7h ld de,conbuf and a sbc hl,de ld b,l ret nz jp ERROR 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 '''' jr z,l0f1eh push hl call expr ld a,l pop hl jr c,l0f42h ld (hl),a inc hl jr l0f3ah l0f1eh: inc de ld a,(de) cp '''' jr z,l0f2bh or a jr z,l0f42h l0f27h: ld (hl),a inc hl jr l0f1eh l0f2bh: inc de ld a,(de) cp '''' jr z,l0f27h cp '.' jr nz,l0f3ah inc de dec hl set 7,(hl) inc hl l0f3ah: pop af jr nc,l0ef9h ld (last_S),hl jr l0ef9h l0f42h: pop af ret nc ld (last_S),hl ret ;------------------------------------------------------------------------------- ; >>D [startaddr] [endaddr] ; Display memory in hex and ASCII cmd_D: ld (cmd_rpt),hl ld hl,(last_D) ld bc,128 call sub_0377h scf sub_0f58h: push bc push de push hl push af l0f5ch: call out_hl_bl2 ld de,0 l0f68h: ld a,(hl) inc hl call out_hex_bl dec bc inc e ld a,e cp 010h jr z,l0f80h and 003h call z,outbl ld a,b or c jr nz,l0f68h l0f80h: call outbl and a sbc hl,de l0f86h: ld a,(hl) call sub_0fa3h call outchar inc hl dec e jr nz,l0f86h pop af push af jr nc,l0f97h ld (last_D),hl l0f97h: call crlf ld a,b or c jr nz,l0f5ch pop af pop hl pop de pop bc ret sub_0fa3h: and 07fh cp 07fh jr z,l0fach cp ' ' ret nc l0fach: ld a,'.' ret ;------------------------------------------------------------------------------- ; > Fcommandline ; specifiy filenames and command line ;cmd_F: ;------------------------------------------------------------------------------- ; > R [displacement] ; Read Intel Hex File from console [add displacement] cmd_R: ld hl,0 call get_lastarg_def ;get offset from command line push hl ld hl,0 ld (high_load),hl w_recstart: call i.getchar jr z,rdhex_done cp ':' jr nz,w_recstart ld c,0 ;init checksum call i.gethexbyte ;record len ld b,a call i.gethexbyte ;address high ld h,a call i.gethexbyte ;address low ld l,a call i.gethexbyte ;record type (ignored) ld a,b and a ;record len == 0? jr z,rdhex_done l16c6h: call i.gethexbyte pop de ;offset push de push hl add hl,de call i.storebyte pop hl inc hl djnz l16c6h ;repeat for record len call i.gethexbyte ;checksum ld a,c and a jr nz,error2 ;exit if checksum error jr w_recstart ;next record rdhex_done: pop hl call i.gethexbyte jp p_max_high 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,error2 call hex_digit ret nc error2: jp ERROR i.getchar: call incharw cp 01ah ret i.storebyte: push af push de ld de,ddtz_base ;don't load over ddtz call cp_hl_de jr nc,ist_1 ld de,(bitmap_end) call cp_hl_de jr nc,error2 ist_1: ld de,(high_load) call cp_hl_de jr c,l1157h ld (high_load),hl l1157h: ld de,(max_load) call cp_hl_de jr c,l1163h ld (max_load),hl l1163h: pop de pop af ld (hl),a ;store byte ret ;------------------------------------------------------------------------------- p_max_high0: call assert_eol p_max_high: call pstr_inl DC 'High = ' ld hl,(high_load) call out_hl_bl2 call pstr_inl DC 'Max = ' ld hl,(max_load) call out_hl_bl2 call pstr_inl DC 'Top = ' ld hl,ddtz_base-1 call out_hl jp crlf ;------------------------------------------------------------------------------- ; > Wstartaddr endaddr ; Write a file to disk ;cmd_W: ;------------------------------------------------------------------------------- ; > A [startaddr] ; Assemble Zilog Z180 mnemonics ;cmd_A: ;------------------------------------------------------------------------------- ; >>L [startaddr] [endaddr] ; List disassembled code cmd_L: ld (cmd_rpt),hl call expr jr nc,l18dbh ld hl,(last_L) l18dbh: call next_arg call get_range jr nc,l1905h call assert_eol ld b,16 l18ebh: push bc call cmdl_p_line pop bc djnz l18ebh ret l1905h: call assert_eol ld d,h ld e,l add hl,bc ex de,hl l190fh: push de call cmdl_p_line pop de call cp_hl_de jr c,l190fh ret ;------------------------------------------------------------------------------- cmdl_p_line: ; push hl call out_hl_bl2 ex de,hl scf call p_disas_instr ex de,hl ld (last_L),hl ret p_disas_instr: push af call dis_decode pop af jr nc,pdinstr_1 ld a,3 sub b jr c,pdinstr_1 inc a ld b,a add a,b add a,b ld b,a pdinstr_0: call outbl djnz pdinstr_0 pdinstr_1: call pstr ;print instruction text jp crlf ;------------------------------------------------------------------------------- ; Enter with DE pointing to the instruction dis_decode: LD BC,0000h PUSH BC pop iy PUSH BC ;workspace (4 bytes) rl c ;carry to c.0 PUSH BC ld c,b ADD iy,SP ;workspace pointer to iy LD HL,GROUP3 TRYNDX: CALL FETCH LD B,C ;First check whether this CP 0EDh ;is an "ED" instruction JR Z,CONFLG ;Yes, clear the index flag INC B ; CP 0DDh JR Z,CONFLG INC B CP 0FDh JR NZ,NOTNDX CONFLG: LD (iy+1),B ;Condition the index flag INC B ;Repeat index tests if the DJNZ TRYNDX ;pre-byte was 0DDH or 0FDH JR NXBYTE ;Otherwise continue NOTNDX: LD C,A ;Save opcode byte; check if LD A,(iy+1) ;index flag was set (allows any OR A ;series of 0DDH and or 0FDH JR Z,NODISP ;bytes, as per Zilog spec) LD A,C ;If so, check for presence CP 0CBh ;of any displacement JR Z,GETDIS ;0CBH needs a displacement AND 044h ;A displacement is required CP 004h ;if opcode has bit 6 reset JR Z,GETDIS ;and bit 2 set LD A,C ;A displacement is required AND 0C0h ;if opcode has bit 6 set CP 040h ;and bit 7 reset JR NZ,NODISP GETDIS: CALL FETCH ;Get displacement if needed LD (iy+2),A ;and save it in workspace NODISP: LD HL,GROUP1 ;"Main" instruction group LD A,C ;Recover opcode and check CP 0CBh ;for 0CBH JR NZ,NEWMSK ;No, start the search LD HL,GROUP2 ;Yes, point to "CB" group NXBYTE: CALL FETCH ;Fetch the last non-data byte LD C,A ;and store it in C NEWMSK: LD A,(HL) ;Fetch a mask from table OR A ;End of table? JR Z,TABEND ; AND C ;Mask opcode INC HL ;-> mode byte NEWMOD: LD B,(HL) ;Fetch mode byte INC HL ;-> match byte INC B ;mode = 0FFH ? JR Z,NEWMSK TRYMAT: CP (HL) ;Is the masked opcode INC HL ;equal to the match byte? JR Z,GETNDX BIT 7,(HL) ;index byte bit 7 is set if INC HL ;address mode changes JR Z,TRYMAT JR NEWMOD ;Change, get a new mode GETNDX: DEC B ;Restore the mode byte LD A,(HL) ;Matched, fetch mnemonic index AND 07Fh ;Z flag TABEND: push af ;save Z flag ld l,a cp i_opc_bli ;block instruction? jr c,tabe_0 ld a,c and 03h add a,l ld l,a ld a,c rra and 0ch jr tabe_1 tabe_0: cp i_opc_alu jr c,tabe_2 bit 7,b jr nz,tabe_2 ld a,c rra rra rra and 07h tabe_1: add a,l tabe_2: PUSH DE ;save source pointer ld hl,disasbuf ;buffer pointer LD de,t_MNEMONICS CALL XTRACT ;copy mnemonic to buffer LD de,disasbuf+5 da_spaces: ld (hl),' ' inc hl call cp_hl_de jr c,da_spaces POP DE ;source pointer pop af jr z,OPDONE1 LD A,B ;test AND 0F0h ;if any "first" operand JR Z,SECOND ;is present RRA RRA RRA RRA PUSH BC ;Save operand byte and opcode LD B,A ;save operand index LD A,C ;get opcode CALL OPRND1 ;process operand POP BC ;Restore operand byte and opcode LD A,B ;Test low-order B for any AND 00Fh ;"second" operand JR Z,OPDONE LD (HL),',' ;comma before second operand INC HL SECOND: LD A,B AND 00Fh LD B,A ;operand index in B LD A,C ;ocode in A CALL NZ,OPRND2 OPDONE: or 0ffh OPDONE1: ld (hl),0 ;Terminate output buffer ld hl,disasbuf ;Return output buffer POP bc ;Discard workspace and POP bc ;put number of bytes fetched in b ret z ;Return carry clear on error scf ret ;------------------------------------------------------------------------------- ; ; GROUP2, GROUP1 and GROUP3 are instruction decoding tables and have ; the following structure: ; ; [ mask { mode ( match , index ) } 0FFH ] 0. ; ; The repeating group ( match , index ) terminates when the MSB of the ; index byte is set. The interpretation of the "mode" byte is ; explained in the documentation to datasheet OPRNDZ. ; ; CB group GROUP2: DB 0C0h,036h ;mask, mode DB 040h,i_BIT ; bit b,g DB 080h,i_RES ; res b,g DB 0C0h,i_SET+80h ; set b,g DB 0FFh ; DB 0F8h,000h ;mask, mode DB 030h,i_?+80h ; (sll g) DB 0FFh ; DB 0C0h,006h ;mask, mode DB 000h,i_RLC+80h ; rlc g ... srl g ; Main group GROUP1: DB 0FFh,000h ;mask, mode DB 000h,i_NOP ; NOP DB 076h,i_HALT ; HALT DB 0C9h,i_RET ; RET DB 0D9h,i_EXX ; EXX DB 0F3h,i_DI ; DI DB 0FBh,i_EI+80h ; EI DB 004h ;mode DB 008h,i_EX+80h ; DB 001h DB 010h,i_DJNZ DB 018h,i_JR+80h DB 0AFh DB 022h,i_LD+80h DB 0FAh DB 02Ah,i_LD+80h DB 0A7h DB 032h,i_LD+80h DB 07Ah DB 03Ah,i_LD+80h DB 003h DB 0C3h,i_JP DB 0CDh,i_CALL+80h DB 097h DB 0D3h,i_OUT+80h DB 079h DB 0DBh,i_IN+80h DB 05Fh DB 0E3h,i_EX+80h DB 00Eh DB 0E9h,i_JP+80h DB 005h DB 0EBh,i_EX+80h ; DB 0DFh DB 0F9h,i_LD+80h DB 0FFh DB 0C0h ;mask DB 0B6h ;mode r[y],r[z] DB 040h,i_LD+80h DB 006h ;mode alu[y],r[z] DB 080h,i_ADD+80h DB 0FFh DB 0C7h ;mask DB 00Bh DB 004h,i_INC ; inc r[y] DB 005h,i_DEC+80h ; dec r[y] DB 0B2h, DB 006h,i_LD+80h ; ld r[y],nn DB 000h ;mode DB 007h,i_RLCA+080h ; rlca ... DB 020h DB 0C0h,i_RET+080h ; ret cc DB 023h DB 0C2h,i_JP ; jp cc,mn DB 0C4h,i_CALL+080h ; call cc,mn DB 010h DB 0C7h,i_RST+080h ; rst DB 002h ;mode alu[y] n DB 0C6h,i_ADD+80h ; add ... DB 0FFh DB 0CFh DB 0D3h DB 001h,i_LD+80h ; ld ww,mn DB 00Dh DB 003h,i_INC ; inc rp DB 00Bh,i_DEC+80h ; dec rp DB 0FDh DB 009h,i_ADD+80h ; add hl,rp DB 060h DB 0C1h,i_POP ; pop rp2 DB 0C5h,i_PUSH+80h ; push rp2 DB 0FFh DB 0E7h DB 021h DB 020h,i_JR+80h ;jr cc, DB 0FFh DB 0EFh DB 0E7h DB 002h,i_LD+80h ; ld (rp),a ;rp=bc,de DB 07Eh DB 00Ah,i_LD+80h ; ld a,(rp) ;rp=bc,de ; ED group GROUP3: DB 0FFh,000h ; DB 044h,i_NEG ; NEG DB 045h,i_RETN ; RETN DB 04Dh,i_RETI ; RETI DB 04Eh,i_? ; (IM 0) DB 067h,i_RRD ; RRD DB 06Fh,i_RLD ; RLD DB 076h,i_SLP ; slp DB 083h,i_OTIM ; otim DB 093h,i_OTIMR ; otimr DB 08Bh,i_OTDM ; otdm DB 09Bh,i_OTDMR ; otdmr DB 031h,i_? ; (OUT0 (m),0) DB 071h,i_?+80h ; (OUT (C),0) DB 009h DB 030h,i_IN0+80h ; in0 (m) DB 002h DB 064h,i_TST ; tst m DB 074h,i_TSTIO+80h ; tstio m DB 080h DB 070h,i_IN+80h ; IN (C) DB 0FFh DB 0C7h DB 00bh DB 004h,i_TST+80h ; tst r DB 0B8h DB 040h,i_IN+80h ; IN r,(C) DB 0B9h DB 000h,i_IN0+80h ; IN0 r,(m) DB 08Bh ; DB 041h,i_OUT+80h ; OUT (C),r DB 09Bh ; DB 001h,i_OUT0+80h ; OUT0 (m),r DB 0FFh ; ; DB 0CFh ; DB 0FDh ; DB 042h,i_SBC ; sbc hl,rp DB 04Ah,i_ADC+80h ; adc hl,rp DB 0ADh ; DB 043h,i_LD+80h ; LD (nn),rp DB 0DAh ; DB 04Bh,i_LD+80h ; LD rp,(nn) DB 00Dh DB 04Ch,i_MLT+80h ;mlt rp DB 0FFh ; ; DB 0E7h ; DB 040h ; DB 046h,i_IM+80h ; IM x DB 0FFh ; ; DB 0F7h ; DB 0C7h ; DB 047h,i_LD+80h ; LD i|r,A DB 07Ch ; DB 057h,i_LD+80h ; LD A,i|r DB 0FFh DB 0E4h ; DB 000h ; DB 0A0h,i_LDI+80h ; LDI ... DB 0FFh ; ; DB 000h ;------------------------------------------------------------------------------- opc macro x i_&x equ opc_index dc '&x' opc_index defl opc_index+1 endm t_MNEMONICS: opc_index defl 0 ; 1-byte other opc ? ; 0 opc NOP ; 1 opc LD ; 2 opc INC ; 3 opc DEC ; 4 opc DJNZ ; 5 opc JR ; 6 opc HALT ; 7 opc RET ; 8 opc POP ; 9 opc JP ;10 opc CALL ;11 opc PUSH ;12 opc RST ;13 opc OUT ;14 opc EXX ;15 opc IN ;16 opc EX ;17 opc DI ;18 opc EI ;19 ; CB bit opc BIT ;20 opc RES ;21 opc SET ;22 ; ED opc NEG ;23 opc RETN ;24 opc RETI ;25 opc IM ;26 opc RRD ;27 opc RLD ;28 ; Z180 opc IN0 ;29 opc OUT0 ;30 opc TST ;31 opc MLT ;32 opc TSTIO ;33 opc SLP ;34 opc OTIM ;35 opc OTDM ;36 opc OTIMR ;37 opc OTDMR ;38 ;opc_index_gap equ 64-opc_index ;opc_index defl 64 i_opc_alu equ opc_index ; 1-byte "alu" opc ADD ;72 opc ADC ;73 opc SUB ;74 opc SBC ;75 opc AND ;76 opc XOR ;77 opc OR ;78 opc CP ;79 ; 1-byte no arguments opc RLCA ;64 opc RRCA ;65 opc RLA ;66 opc RRA ;67 opc DAA ;68 opc CPL ;69 opc SCF ;70 opc CCF ;71 ; CB rot opc RLC ;80 opc RRC ;81 opc RL ;82 opc RR ;83 opc SLA ;84 opc SRA ;85 opc SLL ;86 opc SRL ;87 i_opc_bli equ opc_index ; ED Block instr (bli) opc LDI ;88 opc CPI ;89 opc INI ;90 opc OUTI ;91 opc LDD ;92 opc CPD ;93 opc IND ;94 opc OUTD ;95 opc LDIR ;96 opc CPIR ;97 opc INIR ;98 opc OTIR ;99 opc LDDR ;100 opc CPDR ;101 opc INDR ;102 opc OTDR ;103 ;------------------------------------------------------------------------------- ; ; Disassemble and output Z80 machine code operand ; ; Index OPRND1 OPRND2 ; ----------------------------------------------------------- ; 1 RST address Relative address ; 2 Condition Immediate byte ; 3 Bit number Immediate word ; 4 Interrupt mode AF,AF' ; 5 (SP) DE,HL ; 6 Register pair 8-bit source ; ----------------------------------------------------------- ; 7 A ; 8 (C) ; 9 (port number) ; A (Absolute address) ; B 8-bit destination ; C I or R ; D 16-bit register ; E Address in 16-bit register ; F Index register ; ; Input: ; A: opcode ; B: operand index ; DE: Address of next instruction byte ; HL: Address of next free byte in output buffer ; (iy+0): Bit = 1: Print opcodes ; (iy+1): index register flag (1=IX, 2=IY, else 0) ; (iy+2): displacement for any indexed instruction ; (iy+3): no. of instraction bytes fetched ; ; Output: ; Operand in output buffer ; DE, HL updated ; AF, BC destroyed ; ; ;------------------------------------------------------------------------------- RGSTRS: DC 'B' ; 0 DC 'C' ; DC 'D' ; DC 'E' ; DC 'H' ; DC 'L' ; DC '(C)' ; 6 DC 'A' ; DC 'I' ; 8 DC 'R' ; DC 'AF,AF''' ;10 DC 'DE,HL' ; DC 'BC' ;12 DC 'DE' ; DC 'AF' ; DC 'SP' ; DC 'HL' ;16 DC 'IX' ; DC 'IY' ; DC '(SP)' ;19 DC 'NZ' ;20 DC 'Z' ; DC 'NC' ; DC 'C' ; DC 'PO' ; DC 'PE' ; DC 'P' ; DC 'M' ; DC '0' ;28 DC '?' ; DC '1' ; DC '2' ; ;------------------------------------------------------------------------------- OPRND1: ;First enty point DJNZ CONDIT ;1? ;RSTADR: ;Op1 i1: Mode is RST address AND 038h ; JR DA OPRND2: DJNZ DAT8 ;1? ;RELADR: CALL FETCH ld c,a rla sbc a,a ld b,a ld a,c add a,e ld c,a ld a,b adc a,d jr conv_ac CONDIT: RRA RRA RRA DJNZ BITNUM ;2? ;Op1 i2: Condition BIT 4,A JR NZ,ABS AND 3 ABS: AND 7 ADD A,20 JR PS1 DAT8: DJNZ DAT16 D8: CALL FETCH DA: jr conv_hex BITNUM: DJNZ INTMOD ;3? AND 7 jr conv_dgt DAT16: DJNZ EXAF D16: CALL FETCH LD C,A CALL FETCH conv_ac: call conv_hex ld a,c conv_hex: push af rra rra rra rra call conv_dgt pop af conv_dgt: or 0f0h daa add a,0a0h adc a,040h LD (HL),A INC HL ret ;------------------------------------------------------------------------------- INTMOD: DJNZ STKTOP ;4? AND 3 ADD A,28 PS1: JR PS3 STKTOP: ;5? LD C,19 DEC B JR Z,PS2 ;REG16P: DJNZ COMMON ;?6 RRA AND 3 CP 3 JR NZ,RX DEC A JR RNX EXAF: LD C,10 DEC B JR Z,PS2 ;EXDE: INC C DEC B JR Z,PS2 ;REG8S: DJNZ ACCUM R8: AND 7 CP 6 JR NZ,PS3 LD (HL),'(' INC HL CALL REGX LD A,(iy+1) OR A JR Z,RP LD A,(iy+2) LD (HL),'+' RLCA RRCA JR NC,POS LD (HL),'-' NEG POS: INC HL call DA JR RP ACCUM: RRA RRA RRA COMMON: LD C,7 DEC B ;6? JR Z,PS2 ;PORTC: DEC C DJNZ IDAT8 ;7? PS2: LD A,C PS3: JR PS4 IDAT8: DJNZ IDAT16 ;8? LD (HL),'(' INC HL CALL D8 JR RP IDAT16: DJNZ REG8 ;9? LD (HL),'(' INC HL CALL D16 JR RP REG8: DEC B ;A? JR Z,R8 ;IPAREF: DJNZ REG16 ;B? AND 9 JR PS4 REG16: RRA DJNZ IREG16 ;C? R16: AND 3 RX: CP 2 JR Z,REGX RNX: ADD A,12 JR PS4 IREG16: DJNZ REGX ;D? LD (HL),'(' INC HL CALL R16 RP: LD (HL),')' INC HL RET REGX: LD A,(iy+1) ADD A,16 PS4: PUSH de LD de,RGSTRS CALL XTRACT POP de RET ;------------------------------------------------------------------------------- XTRACT: ex de,hl OR A JR Z,COPY SKIP: BIT 7,(HL) INC HL JR Z,SKIP DEC A JR NZ,SKIP COPY: LD A,(HL) RLCA SRL A LD (DE),A INC DE INC HL JR NC,COPY ex de,hl RET ;------------------------------------------------------------------------------- FETCH: LD A,(DE) bit 0,(iy+0) call nz,out_hex_bl INC (iy+3) LD A,(DE) INC DE RET ;------------------------------------------------------------------------------- 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 ;------------------------------------------------------------------------------- lookup_branch_op: ld a,(hl) and a ret z inc hl and b cp (hl) inc hl ld e,(hl) inc hl ld d,(hl) inc hl jr nz,lookup_branch_op scf ret ;------------------------------------------------------------------------------- tc_set_bp: ld hl,(reg.pc) ld a,h or l jr z,l2037h ld de,BDOS and a sbc hl,de ld hl,l20edh ;set break after BDOS call jr z,l2031h ld de,(reg.pc) call dis_decode jp nc,ERROR ex de,hl call bp_trace_enter ld iy,(reg.pc) ld b,(iy+0) ld c,(iy+1) ld hl,t_op_branch call lookup_branch_op ccf ret c ex de,hl l2031h: call CALL_HL call c,bp_trace_enter l2037h: scf ret ;------------------------------------------------------------------------------- t_op_branch: db 0ffh,0ddh ;Prefix DD dw l20a7h db 0ffh,0fdh ;Prefix FD dw l20ach db 0ffh,0edh ;Prefix ED dw l20b8h db 0ffh,0cdh ;call mn dw l2080h db 0ffh,0c3h ;jp mn dw l208bh db 0ffh,0e9h ;jp () dw l20a2h db 0ffh,0c9h ;ret dw l20dch db 0ffh,0cfh ;rst 8 dw l2115h db 0c7h,0c7h ;rst n dw l20f9h db 0c7h,0c4h ;call cc,mn dw l2080h db 0f7h,010h ;djnz d; jr d dw l2093h db 0e7h,020h ;jr cc,d dw l2093h db 0c7h,0c2h ;jp cc,mn dw l208bh db 0c7h,0c0h ;ret cc dw l20c5h db 0 ;------------------------------------------------------------------------------- ; call mn call cc,mn l2080h: ; jp mn jp cc,mn l208bh: ld l,c ld h,(iy+002h) scf ret ;jr, djnz l2093h: ld a,c rla sbc a,a ld b,a ld hl,(reg.pc) add hl,bc inc hl inc hl scf ret ; jp (hl) l20a2h: ld hl,(reg.l) scf ret ; Prefix DD l20a7h: ld hl,(reg.ix) jr l20afh ; Prefix FD l20ach: ld hl,(reg.iy) l20afh: ld a,c cp 0e9h ; jp (ix); jp (iy) scf ret z and a ret ; Prefix ED l20b8h: ld a,c cp 04dh ; reti jr z,l20dch cp 045h ; retn jr z,l20dch and a ret ;ret cc l20c5h: ld a,b ld (l20d7h),a ld hl,(reg.f) push hl pop af call l20d7h scf jr c,l20dch ret l20d7h: nop and a pop hl inc hl jp (hl) ;ret l20dch: l20edh: ld hl,(reg_sp) ;break on return address ld e,(hl) inc hl ld d,(hl) ex de,hl call bp_trace_enter ;rst 8 l2115h: and a ret ;rst n l20f9h: ld a,(l0003h) cp b ret z ld a,b and 038h ld l,a ld h,000h scf ret ;------------------------------------------------------------------------------- ; >>C[N][J] [steps] ; >>C[N][J] W expression ; >>C[N][J] U expression ; trace over Calls [No list] [Jumps only] /.While./.Until. ;------------------------------------------------------------------------------- ; >>T[N][J] [steps] ; >>T[N][J] W expression ; >>T[N][J] U expression ; Trace [no List] [Jumps only] / .While. / .Until. cmd_T: ld (cmd_rpt),hl ld hl,1 ;default: 1 step call get_lastarg_def ld (trace_cnt_or_ptr),hl call tc_set_bp jr user_go1 l2151h: call bp_clr_temporary ld hl,(trace_cnt_or_ptr) dec hl ld (trace_cnt_or_ptr),hl ld a,h or l jp z,do_break call tc_set_bp jp nc,do_break call p_cpustat user_go1: jp user_go ;------------------------------------------------------------------------------- b_21e2_start: db 0 trace_cnt_or_ptr: dw 0 bp_tab: rept BP_CNT rept BP_SIZE db 0 endm endm ;------------------------------------------------------------------------------- iobyte_cur: db 0ffh last_S: dw TPA last_I: dw 0 last_O_addr: dw 0 last_O_val: db 0 last_D: dw TPA high_load: dw TPA max_load: dw TPA last_L: dw TPA pbl_loop_adr: dw 0addeh bitmap_end: dw 0 ;------------------------------------------------------------------------------- conbuf: ds CONBUF_SIZE+1 disasbuf equ conbuf+1 ;------------------------------------------------------------------------------- rept (STACK_SIZE+3)/4 db 0deh,0adh,0beh,0efh endm stack: reg.l2: db 000h reg.h2: db 000h reg.e2: db 000h reg.d2: db 000h reg.c2: db 000h reg.b2: db 000h reg.f2: db 000h reg.a2: db 000h db 000h reg.i: db 000h reg.iy: dw 0000h reg.ix: dw 0000h reg.f: db 000h reg.a: db 000h reg.c: db 000h reg.b: db 000h reg.e: db 000h reg.d: db 000h reg.l: db 000h reg.h: db 000h reg_sp: dw TPA reg.iff: db 0f3h db 0c3h reg.pc: dw TPA cmd_rpt:dw mainloop db 0ffh,0ffh,0ffh ;------------------------------------------------------------------------------- ddtz_size equ $-ddtz_base prog_size equ $-start ddtz_end: ;------------------------------------------------------------------------------- end