X-Git-Url: http://cloudbase.mooo.com/gitweb/ddt180.git/blobdiff_plain/0c461f1d8b5869c9d263dae1929c3c74c7caa6fd..d0ff7c76b85c1d1f7e76672462c0ba85861ab9b3:/ddt180.z80 diff --git a/ddt180.z80 b/ddt180.z80 index f9a4014..da5cfe6 100644 --- a/ddt180.z80 +++ b/ddt180.z80 @@ -14,6 +14,7 @@ TPA equ 0100h .phase TPA jp start + ds 3 ldr_end: ldr_size equ $ - TPA @@ -57,12 +58,11 @@ BDOS_SETDMA equ 26 ;Set DMA Address ; ddtz specific definitions -STACK_SIZE equ 64 ;ddtz internal stack +STACK_SIZE equ 80 ;ddtz internal stack CONBUF_SIZE equ 80 ;Size of console input buffer EXPR_BUF_SIZE equ 128 ;expressen buffer for conditional breakpoints BP_CNT equ 12 ;Number of breakpoints BP_SIZE equ 8 ;Size of a breakpoint record -YREG_CNT equ 10 ;Number of Y registers (0..9) ;------------------------------------------------------------------------------- @@ -70,7 +70,7 @@ ddtz_base: jp ddtz_bdos l0003h: rst 30h -sub_0004h: +di_or_ei: nop ret ddtz_bdos: @@ -79,7 +79,7 @@ ddtz_bdos: current_cseg defl $ - current_cseg .phase current_phase + current_cseg signon: - db 'Symbolic DDTZ/180' + db 'DDTZ/180' db ' - Version ' maclib version.inc defvers @@ -120,20 +120,18 @@ reg.iff: db 0c3h reg.pc: dw TPA var.$: dw 0000h -var.@: dw 0 -error_func:dw l0146h cmd_rpt:dw mainloop +;------------------------------------------------------------------------------- + conbuf: db CONBUF_SIZE ld sp,stack exx ld de,ddtz_base - or a - sbc hl,de - add hl,de + call cp_hl_de jr c,l0079h ex de,hl l0079h: @@ -155,11 +153,10 @@ l007ch: ld a,0fbh l0093h: ld (reg.iff),a - call sub_0004h + call di_or_ei ld hl,ddtz_base ld l,000h ld (reg_sp),hl - call cpy_fcb2 ld a,(dfcb1+1) cp ' ' ld hl,0 @@ -168,9 +165,11 @@ l0093h: ds CONBUF_SIZE + 3 - ($ - conbuf) +;------------------------------------------------------------------------------- + CMDTAB: - dw cmd_@ ;examine/substitute the displacement register @ - dw cmd_A ;Assemble + dw ERROR ;cmd_@ ;examine/substitute the displacement register @ + dw ERROR ;cmd_A ;Assemble dw cmd_B ;Breakpoints display/set/clear dw cmd_C ;trace over Calls dw cmd_D ;Display memory in hex and ascii @@ -187,25 +186,29 @@ CMDTAB: 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 and/or symbol file + 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 cmd_W ;Write a file to disk dw cmd_X ;eXamine [and substitute] registers - dw cmd_Y ;examine [and substitute] Y variables + dw ERROR ;cmd_Y ;examine [and substitute] Y variables dw cmd_Z ;Zap (fill) memory with a byte string +ERROR: +p_msg_error: + call pstr_inl + dc '?',CR,LF + ;fall thru mainloop: ld sp,stack - ld hl,l0146h - ld (error_func),hl ld hl,(reg.pc) ld (var.$),hl call bp_clr_temporary ld hl,(cmd_rpt) ld de,mainloop + push de call cp_hl_de ld a,'>' call outchar @@ -214,7 +217,8 @@ mainloop: call get_line call skipbl jr z,exe_hl - ld hl,mainloop + pop hl + push hl ld (cmd_rpt),hl inc de sub '@' @@ -228,46 +232,21 @@ mainloop: inc hl ld h,(hl) ld l,a - jr exe_hl -ERROR: - ld hl,(error_func) exe_hl: - call CALL_HL - jr mainloop + jp (hl) + +;------------------------------------------------------------------------------- -l0146h: - call pstr_inl - dc '?' - ;fall thru crlf: call pstr_inl - db CR,LF+80h + dc CR,LF call inchar ld a,0 ld (con_col),a jr c,mainloop ret -out.hl.@: - call out_hl - push de - push hl - ld de,(var.@) - ld a,d - or e - jr z,l01bfh - call outbl - call pstr_inl - dc '@' - and a - sbc hl,de - call out_hl -l01bfh: - pop hl - pop de - ret - sub_01d9h: call pstr_inl dc '-' @@ -277,7 +256,7 @@ sub_01d9h: out_hl_dec_neg: push hl call sub_01d9h - defb 03eh + defb 03eh ;ld a,.. swallow push hl out.hl.dec: push hl ld b,006h @@ -324,12 +303,10 @@ out_hex: pop af out_dgt: - and 0fh - cp 10 - jr c,l0229h - add a,007h -l0229h: - add a,'0' + or 0f0h + daa + add a,0a0h + adc a,040h jr outchar out.bin.w: @@ -339,11 +316,11 @@ out.bin.w: out.bin.b: ld b,8 l01c9h: - add a,a - push af - ld a,00 - adc a,a - call out_dgt + rlca + push af + ld a,'0'/2 + adc a,a + call outchar pop af djnz l01c9h ld a,'"' @@ -385,10 +362,6 @@ outbl: ld a,' ' jr outchar -p_char_lparen: - ld a,'(' - jr outchar - outquote: ld a,'''' outchar: @@ -428,17 +401,6 @@ pstr_inl: ex (sp),hl ret -p_align_@_sym: - push de - ld de,(var.@) - ld a,d - or e - pop de - ld a,(symlen_max) - jr z,$+4 - add a,6 - add a,c - ld c,a p_goto_col: ld a,(con_col) cp c @@ -447,9 +409,10 @@ p_goto_col: call outbl jr p_goto_col - +;------------------------------------------------------------------------------- inchar: + push ix push hl push de push bc @@ -464,6 +427,7 @@ l0284h: pop bc pop de pop hl + pop ix ret get_line: @@ -483,16 +447,21 @@ get_line: pop hl ret +;------------------------------------------------------------------------------- + get_char_upper: ld a,(de) toupper: cp 'a' ret c cp 'z'+1 - ret nc + ccf + ret c and 05fh ret +;------------------------------------------------------------------------------- + skipbl0: inc de skipbl: @@ -517,18 +486,22 @@ assert_eol: to_error: jp ERROR +;------------------------------------------------------------------------------- + chk_stack: push hl push de ld hl,0 add hl,sp - ld de,stack-40 + ld de,stack-(STACK_SIZE-28) call cp_hl_de pop de pop hl jr c,to_error ret +;------------------------------------------------------------------------------- + add_hl_a: add a,l ld l,a @@ -541,83 +514,7 @@ cp_hl_de: sbc hl,de add hl,de ret - -sub_hl_a1: - dec hl -sub_hl_a: - push bc - ld c,a - ld b,0 - or a - sbc hl,bc - pop bc - ret - -sym_getname: - push de - push hl - ld hl,ddtz_base+2 -sgn_l: - ld d,(hl) - dec hl - ld e,(hl) - dec hl - ld a,(hl) - cp 0c3h - jr z,sgn_e - - ex (sp),hl - call cp_hl_de - jr z,sgn_e - ex (sp),hl - call sub_hl_a1 - jr sgn_l -sgn_e: - sub 0c3h - pop hl - pop de - ret - -p_symstr: - push bc - ld b,(hl) -pss_l: - dec hl - ld a,(hl) - call outchar - djnz pss_l - dec hl - pop bc - ret - -p_symbol: - if 0 - ld a,(dash_flag) - or a - ret nz - endif - push hl - call sym_getname - call nz,p_symstr - pop hl - ret - -p_label: - if 0 - ld a,(dash_flag) - or a - ret nz - endif - push hl - call sym_getname - jr z,pl_e - call p_symstr - call pstr_inl - dc ':' - call crlf -pl_e: - pop hl - ret +;------------------------------------------------------------------------------- lookupch: ld b,0 @@ -637,12 +534,8 @@ l0300h: ret sub_0303h: - ld hl,b_0cc3_start + ld hl,t_reg_names ld b,07fh - jr l030ch - -sub_030ah: - ld b,0ffh l030ch: inc b ld a,(hl) @@ -653,10 +546,6 @@ l030ch: res 7,b ret -sub_0318h: - push bc - res 7,b - defb 03eh ;ld a,nn sub_031ch: push bc push de @@ -743,7 +632,7 @@ sub_0377h: jr l0366h b_037c_start: - defb 0e6h + defb 0e6h ;and a,.. clear carry get_arg_range: scf ex af,af' @@ -755,7 +644,7 @@ get_arg_range: jr c,error0 ex af,af' pop hl - defb 03eh + defb 03eh ;ld a,.. swallow pop af l038ch: pop af call get_range @@ -801,6 +690,8 @@ l03b8h: scf ret +;------------------------------------------------------------------------------- + expr: call skipbl expr1: @@ -820,6 +711,8 @@ expr1: pop de ret +;------------------------------------------------------------------------------- + do_op_eq: jr z,l03edh jr l03ech @@ -958,40 +851,33 @@ doop_mod: ; de: r (x%y) div_hl_de: - push bc - ex de,hl - ld b,h - ld c,l - ld hl,0 - ld a,16 + push bc + ex de,hl ;de: x + 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) -l047eh: - push af - add hl,hl - ex de,hl - xor a - add hl,hl - ex de,hl - adc a,l - sub c - ld l,a - ld a,h - sbc a,b - ld h,a - inc de - jr nc,l048fh - add hl,bc - dec de -l048fh: - pop af - dec a - jr nz,l047eh - ex de,hl - pop bc +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: @@ -1049,6 +935,8 @@ tblf_opa: dw doop_xor dw 0 +;------------------------------------------------------------------------------- + fact_factor: call do_factor ret nc @@ -1071,12 +959,12 @@ do_factor: ld hl,TPA cp 'L' ret z - ld hl,(var.@) - cp '@' - ret z ld hl,(var.$) cp '$' ret z + ld hl,ddtz_base + cp 'Z' + ret z cp '-' jr z,fact_factneg cp '~' @@ -1085,34 +973,17 @@ do_factor: jr z,fact_factor cp '^' jr z,fact_reg.CPU - cp 'Y' - jr z,fact_reg.Y cp '(' jr z,fact_mem cp '[' jr z,expr_brckt cp '''' jr z,fact_factstring - cp '.' - jr z,fact_symbol dec de scf ret -fact_reg.Y: - call get.decdigit - jr c,error1 - inc de -get_y_val: - 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 @@ -1198,45 +1069,7 @@ expr_brckt: error1: jp ERROR -fact_symbol: - push bc - ld hl,ddtz_base ;symtbl start - -fs_nxtsym: - ld a,(hl) ;symlen - cp 0c3h - jr z,error1 - ld b,a ;symlen - inc b - push hl ;symtbl ptr - push de ;inpsym ptr -fs_2: - ld a,(de) - djnz fs_3 - call test_sym_char - jr z,fs_cont - pop hl ;inpsym ptr (discard) - pop hl ;symtbl ptr - inc hl - ld a,(hl) ;symval h - inc hl - ld h,(hl) ;symval l - ld l,a - or a ;clear carry - pop bc - ret -fs_3: - inc de - dec hl - cp (hl) - jr z,fs_2 -fs_cont: ;start over - pop de ;inpsym ptr - pop hl ;symtbl ptr - ld a,(hl) - add a,3 - call sub_hl_a - jr fs_nxtsym +;------------------------------------------------------------------------------- get.number: call get.hexdigit @@ -1281,7 +1114,7 @@ l05dbh: jr next_bindigit l05e4h: cp '"' - jp nz,ERROR + jr nz,error11 call get.bindigit jr nc,l05dbh or a @@ -1306,11 +1139,12 @@ next_decdigit: decnum_done: cp '.' ret z +error11: jp ERROR sub_060ch: call get_char_upper - cp '[' + cp 'Z'+1 jr l0614h get.hexdigit: @@ -1343,6 +1177,8 @@ l0625h: sub '0' ret +;------------------------------------------------------------------------------- + p_cpustat0: call assert_eol p_cpustat: @@ -1354,6 +1190,7 @@ p_cpustat: l063eh: call p_regs djnz l063eh + call outbl6 push hl push de ld iy,(reg.pc) @@ -1370,8 +1207,6 @@ l065bh: djnz l065bh pop af pop hl - call nz,outbl6 - call nz,p_offset jp crlf p_f: @@ -1388,24 +1223,25 @@ p_f2: jp outbl p_flags: - ld b,a - ld a,'S' - call sub_06aah - ld a,'Z' - call sub_06aah - rl b - ld a,'H' - call sub_06aah - rl b - ld a,'V' - call sub_06aah - ld a,'N' - call sub_06aah - ld a,'C' -sub_06aah: - rl b - jp c,outchar - jp outbl + 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 @@ -1427,12 +1263,6 @@ p_regs: inc hl ld d,(hl) ex de,hl - dec a - jr z,l06d9h - call out.hl.@ - call z,outbl6 - jr l06e2h -l06d9h: call out_hl jr l06e2h l06deh: @@ -1489,36 +1319,75 @@ b_0709_start: db 000h db 000h +;------------------------------------------------------------------------------- +; > G [startaddr] [;breakp..] +; Go [to start] [with temporary breakpoints] + cmd_G: sub a ld (trace_call_flag),a - ld (l0941h),a + ld (bp_p_cpu_flag),a call expr jr c,l0740h ld (reg.pc),hl l0740h: call skipbl - jp z,user_go + 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: - ld b,BP_CNT - ld ix,bp_tab -l075ah: + call bpl_init + ld a,(ix+000h) and 0f1h ld (ix+000h),a call bp_clr_condition - ld de,BP_SIZE - add ix,de - djnz l075ah + + call bpl_next ret +;------------------------------------------------------------------------------- +; > B +; display all breakpoints +; > B breakp [breakp..] +; set breakpoints +; > BX +; clear all breakpoints +; > BX address [address..] +; clear breakpoints +; +; where breakp is: +; [R] expression [I condition] + cmd_B: call skipbl jr z,bp_print @@ -1528,6 +1397,7 @@ cmd_B: dec de ld a,001h jp bp_enter + bp_clr0: call skipbl jr z,bp_clr_all @@ -1543,9 +1413,8 @@ bp_clr_next: bp_clr_all: scf bp_clr: - ld b,BP_CNT - ld ix,bp_tab -l0799h: + call bpl_init + push af jr c,l07a7h ld e,(ix+002h) @@ -1556,16 +1425,13 @@ l07a7h: ld (ix+000h),000h call bp_clr_condition l07aeh: - ld de,BP_SIZE - add ix,de pop af - djnz l0799h + call bpl_next ret bp_print: - ld b,BP_CNT - ld ix,bp_tab -bp_pr_l: + call bpl_init + bit 0,(ix+000h) jr z,bp_pr_cont ld a,'R' @@ -1577,13 +1443,9 @@ l07cdh: call outbl ld l,(ix+002h) ld h,(ix+003h) - call out.hl.@ - call outbl - call p_symbol - ld c,9 - call p_align_@_sym + call out_hl call pstr_inl - dc ':' + dc ' :' ld l,(ix+004h) ld h,(ix+005h) call out_hl @@ -1599,11 +1461,10 @@ l07cdh: l0805h: call crlf bp_pr_cont: - ld de,BP_SIZE - add ix,de - djnz bp_pr_l + call bpl_next ret +;------------------------------------------------------------------------------- ; Add break points to list ; A = 1 Permanent (B command) ; A = 2 Temporary (G command) @@ -1619,7 +1480,7 @@ bp_enter: bp_e_1: push bc call expr - jp c,ERROR + jr c,error12 pop bc bit 0,b push bc @@ -1644,17 +1505,14 @@ bp_e_1: jr bp_enter bp_get_freeslot: - ld b,BP_CNT - ld ix,bp_tab -bp_gf_l: + call bpl_init + ld a,(ix+000h) and 00fh ret z - push bc - ld bc,BP_SIZE - add ix,bc - pop bc - djnz bp_gf_l + + call bpl_next +error12 jp ERROR bp_get_count: @@ -1664,7 +1522,7 @@ bp_get_count: ret nz inc de call expr - jp c,ERROR + jr c,error12 ret bp_get_condition: @@ -1676,7 +1534,7 @@ bp_get_condition: call skipbl push de call expr - jp c,ERROR + jr c,error12 ex de,hl pop de push de @@ -1688,20 +1546,21 @@ bp_get_condition: add hl,bc ld de,expr_bufe call cp_hl_de - jp nc,ERROR - pop hl - ld (expr_p2),hl - pop de - ex de,hl + jr nc,error12 + pop de + pop hl + push de ldir - xor a - ld (de),a - inc de ex de,hl + ld (hl),c ; trailing 0 + inc hl ld (expr_p1),hl - ld hl,(expr_p2) + pop hl ret +;------------------------------------------------------------------------------- +; Breakpoint handling routine. + bpddtz: ld (reg.l),hl pop hl @@ -1715,13 +1574,13 @@ bpddtz: push ix push iy ld a,i - call sub_0004h + call di_or_ei ld h,a ld l,000h push hl - ld a,0f3h + ld a,0f3h ; EI jp po,l08dfh - ld a,0fbh + ld a,0fbh ; DI l08dfh: ld (reg.iff),a ex af,af' @@ -1730,18 +1589,18 @@ l08dfh: push bc push de push hl - call sub_097ah + call bp_restore_mem ld a,(b_21e2_start) dec a jr z,l090bh - call inchar - jr c,l0902h + call inchar ;Keyboard hit? + jr c,do_break ;yes call sub_0913h and a jp z,user_go and 083h jp z,l2151h -l0902h: +do_break: call bp_clr_temporary call p_cpustat jp mainloop @@ -1755,10 +1614,9 @@ sub_0913h: ld a,080h ex af,af' sub a - ld (l0941h),a - ld b,BP_CNT - ld ix,bp_tab -l0920h: + ld (bp_p_cpu_flag),a + call bpl_init + ld a,(ix+000h) and 007h jr z,l0938h @@ -1770,9 +1628,8 @@ l0920h: call z,sub_0942h pop bc l0938h: - ld de,BP_SIZE - add ix,de - djnz l0920h + + call bpl_next ex af,af' ret @@ -1801,7 +1658,7 @@ l0969h: bit 4,(ix+000h) ret z ld a,001h - ld (l0941h),a + ld (bp_p_cpu_flag),a ret l0974h: ex af,af' @@ -1809,10 +1666,9 @@ l0974h: ex af,af' ret -sub_097ah: - ld b,BP_CNT - ld ix,bp_tab -l0980h: +bp_restore_mem: + call bpl_init + bit 5,(ix+000h) res 5,(ix+000h) jr z,l099ah @@ -1825,32 +1681,28 @@ l0980h: ld (hl),a l099ah: res 3,(ix+000h) - ld de,BP_SIZE - add ix,de - djnz l0980h + + call bpl_next ret -sub_09a6h: - ld b,BP_CNT - ld ix,bp_tab -l09ach: +bp_tst_@pc: + call bpl_init + ld a,(ix+000h) and 003h - jr z,l09c0h + jr z,bp_tst_e ld e,(ix+002h) ld d,(ix+003h) ld hl,(reg.pc) call cp_hl_de ret z -l09c0h: - ld de,BP_SIZE - add ix,de - djnz l09ach +bp_tst_e: + call bpl_next sub a inc a ret -sub_09cah: +bp_trace_enter: call bp_get_freeslot ld (ix+004h),001h ld (ix+005h),000h @@ -1861,16 +1713,15 @@ sub_09cah: ld a,(b_21e2_start) and a ld a,008h - jr nz,l09edh - ld a,004h -l09edh: + jr nz,bp_t_e + rra +bp_t_e: ld (ix+000h),a ret -sub_09f1h: - ld b,BP_CNT - ld ix,bp_tab -l09f7h: +bp_set_to_mem: + call bpl_init + ld a,(ix+000h) and c jr z,l0a1dh @@ -1891,26 +1742,27 @@ l09f7h: inc hl ld (hl),d l0a1dh: - ld de,BP_SIZE - add ix,de - djnz l09f7h + + call bpl_next ret +;------------------------------------------------------------------------------- + user_go: sub a ld (b_21e2_start),a - ld a,(l0941h) + ld a,(bp_p_cpu_flag) and a call nz,p_cpustat - call sub_09a6h + call bp_tst_@pc ld c,007h jr nz,l0a41h ld a,001h ld (b_21e2_start),a - call sub_1ffeh + call tc_set_bp ld c,008h l0a41h: - call sub_09f1h + call bp_set_to_mem ld sp,reg.l2 pop hl pop de @@ -1929,6 +1781,8 @@ l0a41h: ld sp,(reg_sp) jp reg.iff +;------------------------------------------------------------------------------- + bp_clr_condition: ld a,(ix+000h) and 003h @@ -1981,53 +1835,20 @@ l0ab0h: ld (iy+007h),d ret -cmd_Y: - call get.decdigit - jr c,l0bc3h - inc de - push af - call assert_eol - pop af - call sub_0bdch - jp l0c15h -l0bc3h: - call assert_eol - xor a -l0bc7h: - push af - call sub_0bdch - call outbl - pop af - push af - call get_y_val - call p_symbol - pop af - inc a - push af - rra - push af - ld c,11 - call c,p_align_@_sym - pop af - call nc,crlf - pop af - cp YREG_CNT - jr c,l0bc7h - ret +;------------------------------------------------------------------------------- +; > 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 -sub_0bdch: - 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 l0c33h cmd_X: call skipbl @@ -2042,11 +1863,11 @@ cmd_X: cp 01dh jp z,ERROR ex de,hl - ld hl,b_0cc3_start + ld hl,t_reg_names call sel_dc_string l0c12h: call l0c33h -l0c15h: + call outbl push de push bc @@ -2080,9 +1901,7 @@ l0c33h: ld a,(de) dec de ld h,a - bit 1,c - jp z,out_hl - jp out.hl.@ + jp out_hl l0c4fh: call p_f @@ -2101,43 +1920,41 @@ l0c5fh: sub_0c6ah: push af - ld b,000h 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,b_0ca4_start + ld hl,t_flag_names call lookupch jp nc,ERROR - ld a,b - cp 008h - jr z,l0c97h - pop bc - rlca - rlca - rlca - add a,0c0h - ld (l0c94h),a - defb 0cbh -l0c94h: - defb 0c0h + 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 - pop bc jr l0c76h -b_0ca4_start: +t_flag_names: db 'CNV H ZSE',0 sub_0caeh: @@ -2157,7 +1974,7 @@ sub_0caeh: scf ret -b_0cc3_start: +t_reg_names: DC 'BC''' DC 'DE''' DC 'HL''' @@ -2258,12 +2075,16 @@ b_0cfa_start: 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 out_hl call outbl ld a,(hl) call out_hex @@ -2294,18 +2115,17 @@ l0d8ah: call sub_0ef8h jr l0d60h -cmd_@: - call assert_eol - ld hl,msg_@ - ld de,var.@ - ld c,001h - jp l0c12h +;------------------------------------------------------------------------------- +; > @ +; examine (substitute) displacement register @ -msg_@: - dc '@' +;cmd_@: + +;------------------------------------------------------------------------------- +; >>I [port] +; Input a byte from port cmd_I: - ld hl,cmd_I ld (cmd_rpt),hl ld hl,(last_I) call get_lastarg_def @@ -2320,8 +2140,11 @@ cmd_I: call out.bin.b jp crlf +;------------------------------------------------------------------------------- +; >>O [byte] [port] +; Output a byte to a port + cmd_O: - ld hl,cmd_O ld (cmd_rpt),hl ld hl,(last_O_val) call get_arg_def @@ -2338,6 +2161,10 @@ cmd_O: out (c),a ret +;------------------------------------------------------------------------------- +; > Vstartaddr endaddr targetaddr +; Verify (compare) two memory areas + cmd_V: call sub_034eh l0dedh: @@ -2347,7 +2174,7 @@ l0dedh: cp b jr z,l0e10h ld c,a - call out.hl.@ + call out_hl call outbl ld a,b call out_hex @@ -2356,7 +2183,7 @@ l0dedh: call out_hex call outbl ex de,hl - call out.hl.@ + call out_hl ex de,hl call crlf l0e10h: @@ -2369,6 +2196,10 @@ l0e10h: jr nz,l0dedh ret +;------------------------------------------------------------------------------- +; > M[V] startaddr endaddr destaddr +; Move memory [and verify] + cmd_M: call get_char_upper cp 'V' @@ -2399,31 +2230,17 @@ cmdm_up: jr z,l0dedh ret -cmd_H: - call get_char_upper - cp 'S' - jr z,p_sym_list +;------------------------------------------------------------------------------- +; > 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 next_arg - push hl - call expr - push af call assert_eol - pop af - ex de,hl - pop hl - jr c,l0e5eh - push hl - push de - add hl,de - call l0e5eh - pop de - pop hl - and a - sbc hl,de -l0e5eh: call out_hl call outbl2 call out_hl_neg @@ -2433,55 +2250,14 @@ l0e5eh: call out_hl_dec_neg call outbl4 call out.bin.w - call outbl + call outbl2 ld a,l call out.ascii - call outbl2 - call p_symbol jp crlf -p_sym_list: - inc de - call assert_eol - ld a,(symlen_max) - add a,7 - ld b,a - ld c,0 - ld hl,ddtz_base+2 -psym_nxtsym: - ld d,(hl) - dec hl - ld e,(hl) - dec hl - ld a,(hl) - cp 0c3h - jr z,psym_e - - call p_goto_col - ex de,hl - call out_hl - call outbl - ex de,hl - call p_symstr - - ld a,c - add b - ld c,a - ld a,80 ;screen width - sub b - cp c - jr nc,psym_nxtsym - - call crlf - ld c,0 - jr psym_nxtsym - -psym_e: - ld a,c - or a - ret z - jp crlf - +;------------------------------------------------------------------------------- +; > Q[J] startaddr endaddr bytes +; Query memory for a byte string [Justified] cmd_Q: call get_char_upper @@ -2522,6 +2298,10 @@ l0eb0h: pop bc ret +;------------------------------------------------------------------------------- +; > Z startaddr endaddr bytes +; Zap (fill) memory with a byte string + cmd_Z: call get_arg_range push bc @@ -2549,7 +2329,7 @@ sub_0ed7h: push de push bc l0edah: - call get_char_upper + ld a,(de) cp (hl) jr nz,l0ee2h inc de @@ -2635,8 +2415,11 @@ l0f42h: ld (last_S),hl ret +;------------------------------------------------------------------------------- +; >>D [startaddr] [endaddr] +; Display memory in hex and ASCII + cmd_D: - ld hl,cmd_D ld (cmd_rpt),hl ld hl,(last_D) ld bc,128 @@ -2648,7 +2431,7 @@ sub_0f58h: push hl push af l0f5ch: - call out.hl.@ + call out_hl call z,outbl2 call outbl ld de,0 @@ -2703,6 +2486,10 @@ l0fach: ld a,'.' ret +;------------------------------------------------------------------------------- +; > Fcommandline +; specifiy filenames and command line + cmd_F: push de ld hl,DMA_BUF+1 @@ -2722,16 +2509,8 @@ l0fb6h: ld de,dfcb1 call parse_filename ld de,dfcb2 - call parse_filename ;fall thru -cpy_fcb2: - ld hl,dfcb2 - ld de,fcbsym - ld bc,16 - ldir - ret - parse_filename: call sub_102ch push de @@ -2800,6 +2579,7 @@ sub_1012h: cp '.' ret z ld c,'?' + call toupper cp '*' ret @@ -2831,6 +2611,8 @@ sub_1043h: cp ',' ret +;------------------------------------------------------------------------------- + setup_fcb: push de ld hl,12 @@ -2847,6 +2629,8 @@ l1052h: pop de ret +;------------------------------------------------------------------------------- + file_open: ld (cur_fcb),de call setup_fcb @@ -2954,31 +2738,15 @@ hex_digit_v: error2: jp ERROR -read_hexbyte: - call read_byte -read_hexbyte0: - push bc - call hex_digit_v - rlca - rlca - rlca - rlca - ld c,a - call read_byte - call hex_digit_v - or c - pop bc - ret +;------------------------------------------------------------------------------- +; > R [displacement] +; Read a binary or hex file [add displacement] cmd_R: ld hl,0 call get_lastarg_def read_file: - ld de,dfcb1+1 - ld a,(de) - cp '?' - jr z,read_symfile - dec de + ld de,dfcb1 push hl ld hl,0 ld (high_load),hl @@ -2996,7 +2764,7 @@ l108eh: call read_sector jr nz,read_file_nxt pop hl - jr read_symfile + jp p_max_high read_file_nxt: ld de,DMA_BUF @@ -3040,157 +2808,20 @@ l10cch: call read_hexchar ; CHKSUM ld a,c and a - jr nz,error3 + jp nz,ERROR jr l10aeh rdhex_done: pop hl - jr read_symfile - -read_symfile: - ld de,fcbsym+1 - ld a,(de) - cp ' ' - jp z,p_max_high - - push hl ; offset - call pstr_inl - db 'SYMBOLS',CR,LF+80h - - dec de - call file_open -rs_1: - call read_byte -rs_2: - pop de ; offset - cp 1ah - jp z,p_max_high - push de ; offset - cp '!' - jr c,rs_1 - call read_hexbyte0 ; symval H - ld h,a - call read_hexbyte ; symval L - ld l,a - add hl,de - call read_byte - cp ' ' - jr z,rs_4 -rs_3: call read_byte - cp ' ' - jr nc,rs_3 - jr rs_2 - -rs_4: - push hl ; symval - ld hl,(BDOS+1) ; - ld b,0 ; setup symlen -rs_5: - dec hl ; - call read_byte ; next char of symbol name - call test_sym_char ; valid char? - jr nz,rs_6 - ld (hl),a ; - inc b ; symlen++ - ld a,b ; - cp 10h+1 ; - jr c,rs_5 ; -error3: - jp ERROR ; - -rs_6: - call test_symterm_ch - jr nz,error3 - - push bc ; symlen - ex de,hl ; - ld hl,(BDOS+1) ; - inc hl ; - ld c,(hl) ; - inc hl ; - ld b,(hl) ; - ex de,hl - ld (hl),b ; - dec hl ; - ld (hl),c ; - dec hl ; - ld (hl),0c3h ; - - ld de,(max_load) ; - call cp_hl_de ; - jr c,error3 ; - ld de,(reg_sp) ; - call cp_hl_de ; - jr nc,rs_61 ; - ld (reg_sp),hl ; -rs_61: - ld de,(BDOS+1) ; - ld (BDOS+1),hl ; - ex de,hl ; - pop af ; symlen - ld (hl),a ; - inc hl ; - pop de ; symval - ld (hl),e ; - inc hl ; - ld (hl),d ; - ld hl,symlen_max ; - cp (hl) ; new max? - jr c,$+3 ; - ld (hl),a ; - jp rs_1 ; - - -; test for valid character for symbols -; return z if valid - -test_sym_char: - cp '$' - ret z - cp '%' - ret z - cp '.' - ret z - cp '_' - ret z - call test_alphanum - ret c ; cy == 1 --> z == 0 - cp a ; return z - ret - - -; check if char is in [0..9,?,@,A..Z,a..z] -; return cy if invalid -; return nc if valid alfanumeric char - -test_alphanum: - cp 'z'+1 - ccf - ret c - cp 'a' - ret nc - cp 'Z'+1 - ccf - ret c - cp '?' - ret nc -test_numeral: - cp '9'+1 - ccf - ret c - cp '0' - ret + jp p_max_high -test_symterm_ch: - cp CR - ret z - cp LF - ret z test_whitespace: cp ' ' ret z cp TAB ret +;------------------------------------------------------------------------------- + p_max_high0: call assert_eol p_max_high: @@ -3208,6 +2839,10 @@ p_max_high: call out_hl jp crlf +;------------------------------------------------------------------------------- +; > Wstartaddr endaddr +; Write a file to disk + cmd_W: call get_arg_range call assert_eol @@ -3240,1196 +2875,64 @@ l11cch: or c jr z,close_file push bc - ld de,080h ; DMA_BUF - ld b,d - ld c,e - ldir - call write_sector - ex (sp),hl - ld bc,0ff80h - add hl,bc - ex (sp),hl - pop bc - jr l11cch - -write_sector: - push hl - ld de,dfcb1 - ld c,BDOS_WRITE - call ddtz_bdos - pop hl - and a - ret z - call close_file -error4: - jp ERROR - -close_file: - ld de,dfcb1 - ld c,BDOS_CLOSE - jp ddtz_bdos - -cmd_A: - ld hl,(last_A) - call get_lastarg_def - ld (last_A),hl - ld (cmd_A_prev),hl - ld hl,cmda_restart - ld (error_func),hl - ld (l1262h),sp -cmda_loop: - ld hl,(last_A) - ld (var.$),hl - push hl - call p_disas_line - ld c,19 - call p_align_@_sym - ld c,b - push bc - call get_line - pop bc - pop hl - call skipbl - cp '.' - ret z - cp '-' - jr nz,l124bh - ld hl,(cmd_A_prev) - jr cmda_lpend -l124bh: - push hl - pop iy - push hl - and a - call nz,asemble_line - ld b,0 - pop hl - ld (cmd_A_prev),hl - add hl,bc -cmda_lpend: - ld (last_A),hl - jr cmda_loop - -cmda_restart: - call l0146h - ld sp,(l1262h) - jr cmda_loop - -asemble_line: - call skipbl - ld hl,t_MNEMONICS - call sub_030ah - jr nc,error4 - call skipbl - push de - ld a,b - add a,b - add a,b - ld hl,b_1289_start - call add_hl_a - ld e,(hl) - inc hl - ld d,(hl) - inc hl - ld b,(hl) - ex de,hl - pop de - -CALL_HL: - jp (hl) - -b_1289_start: - dw as.ADC_SBC ;ADC - db 088h ; - dw as.ADD ;ADD - db 080h ; - dw as.AND_CP_OR_SUB_XOR ;AND - db 0a0h ; - dw as.BITOP ;BIT - db 040h ; - dw as.CALL ;CALL - db 0c4h ; - dw as.opc.noarg ;CCF - db 03fh ; - dw as.AND_CP_OR_SUB_XOR ;CP - db 0b8h ; - dw gen.opc.ED2 ;CPD - db 0a9h ; - dw gen.opc.ED2 ;CPDR - db 0b9h ; - dw gen.opc.ED2 ;CPI - db 0a1h ; - dw gen.opc.ED2 ;CPIR - db 0b1h ; - dw as.opc.noarg ;CPL - db 02fh ; - dw as.opc.noarg ;DAA - db 027h ; - dw as.DEC_INC ;DEC - db 005h ; - dw as.opc.noarg ;DI - db 0f3h ; - dw as.DJNZ ;DJNZ - db 010h ; - dw as.opc.noarg ;EI - db 0fbh ; - dw as.EX ;EX - db 0e3h ; - dw as.opc.noarg ;EXX - db 0d9h ; - dw as.opc.noarg ;HALT - db 076h ; - dw as.IM ;IM - db 046h ; - dw as.IN ;IN - db 040h ; - dw as.DEC_INC ;INC - db 004h ; - dw gen.opc.ED2 ;IND - db 0aah ; - dw gen.opc.ED2 ;INDR - db 0bah ; - dw gen.opc.ED2 ;INI - db 0a2h ; - dw gen.opc.ED2 ;INIR - db 0b2h ; - dw as.JP ;JP - db 0c2h ; - dw as.JR ;JR - db 020h ; - dw as.LD ;LD - db 040h ; - dw gen.opc.ED2 ;LDD - db 0a8h ; - dw gen.opc.ED2 ;LDDR - db 0b8h ; - dw gen.opc.ED2 ;LDI - db 0a0h ; - dw gen.opc.ED2 ;LDIR - db 0b0h ; - dw gen.opc.ED2 ;NEG - db 044h ; - dw as.opc.noarg ;NOP - db 000h ; - dw as.AND_CP_OR_SUB_XOR ;OR - db 0b0h ; - dw gen.opc.ED2 ;OTDR - db 0bbh ; - dw gen.opc.ED2 ;OTIR - db 0b3h ; - dw as.OUT ;OUT - db 041h ; - dw gen.opc.ED2 ;OUTD - db 0abh ; - dw gen.opc.ED2 ;OUTI - db 0a3h ; - dw as.POP_PUSH ;POP - db 0c1h ; - dw as.POP_PUSH ;PUSH - db 0c5h ; - dw as.BITOP ;RES - db 080h ; - dw as.RET ;RET - db 0c0h ; - dw gen.opc.ED2 ;RETI - db 04dh ; - dw gen.opc.ED2 ;RETN - db 045h ; - dw as.SHIFTOP ;RL - db 010h ; - dw as.opc.noarg ;RLA - db 017h ; - dw as.SHIFTOP ;RLC - db 000h ; - dw as.opc.noarg ;RLCA - db 007h ; - dw gen.opc.ED2 ;RLD - db 06fh ; - dw as.SHIFTOP ;RR - db 018h ; - dw as.opc.noarg ;RRA - db 01fh ; - dw as.SHIFTOP ;RRC - db 008h ; - dw as.opc.noarg ;RRCA - db 00fh ; - dw gen.opc.ED2 ;RRD - db 067h ; - dw as.RST ;RST - db 0c7h ; - dw as.ADC_SBC ;SBC - db 098h ; - dw as.opc.noarg ;SCF - db 037h ; - dw as.BITOP ;SET - db 0c0h ; - dw as.SHIFTOP ;SLA - db 020h ; - dw as.SHIFTOP ;SRA - db 028h ; - dw as.SHIFTOP ;SRL - db 038h ; - dw as.AND_CP_OR_SUB_XOR ;SUB - db 090h ; - dw as.AND_CP_OR_SUB_XOR ;XOR - db 0a8h ; - - dw as.IN0 ;IN0 - db 000h ; - dw as.MLT ;MLT - db 04ch ; - dw gen.opc.ED2 ;OTDM - db 08bh ; - dw gen.opc.ED2 ;OTDMR - db 09bh ; - dw gen.opc.ED2 ;OTIM - db 083h ; - dw gen.opc.ED2 ;OTIMR - db 093h ; - dw as.OUTO ;OUT0 - db 001h ; - dw gen.opc.ED2 ;SLP - db 076h ; - dw as.TST ;TST - db 004h ; - dw as.TSTIO ;TSTIO - db 074h ; - -as.TST: - call arg.r_HL_A ; - jr nc,as.tst_0 - rlca - rlca - rlca - add a,b - ld b,a - jp gen.opc.ED2 -as.tst_0: - ld b,064h -as.TSTIO: - call arg.imm_8bit ; - jr as.store_io0 - -as.IN0: - call arg.r_HL_A ; - jr nc,error5 - cp 006h - jr z,error5 - rlca - rlca - rlca - add a,b - ld b,a - call assert_comma ; - call arg.addr_8bit ; - jr as.store_io0 - -as.OUTO: - call arg.addr_8bit ; - call assert_comma ; - call arg.r_HL_A ; - jr nc,error5 - cp 006h - jr z,error5 - rlca - rlca - rlca - add a,b - ld b,a - -as.store_io0: - call assert_eol - ld (iy+000h),0edh - ld (iy+001h),b - ld (iy+002h),l - ld c,003h - ret - -as.MLT: - call arg.ww ; - jr nc,error5 - add a,b - ld b,a - jp gen.opc.ED2 - -error5: - jp ERROR - -as.LD: - call arg.r_HL_A - jr c,l13d4h - call arg.IDX_displcmnt - jp c,l1471h - call arg.ww - jp c,l149ch - call arg.IX_IY - jp c,l14f5h - call get_char_upper - cp 'I' - jp z,l1511h - cp 'R' - jp z,l1519h - cp '(' - jr nz,error5 - inc de - call arg.ww - jp c,l1528h - call test_expr - call test_paren_close - call assert_comma - call arg.ww - jr c,l13c2h - call arg.IX_IY - jr nc,l13aah - ld b,022h -l1395h: - call assert_eol - ld a,(prefix_ixiy) -l139bh: - ld (iy+000h),a - ld (iy+001h),b - ld (iy+002h),l - ld (iy+003h),h - ld c,004h - ret - -l13aah: - call get_char_upper - cp 'A' - jr nz,error5 - inc de - ld b,032h - -as.store_3: - call assert_eol - ld (iy+000h),b - ld (iy+001h),l - ld (iy+002h),h - ld c,003h - ret - -l13c2h: - cp 020h - jr z,l13d0h - add a,043h - ld b,a -l13c9h: - call assert_eol - ld a,0edh - jr l139bh -l13d0h: - ld b,022h - jr as.store_3 - -l13d4h: - ld b,a - call assert_comma - call arg.r_HL_A - jr nc,l13f0h - push af - ld a,b - rlca - rlca - rlca - ld b,a - pop af - add a,b - add a,040h - cp 076h - jr z,error60 -l13ech: - ld b,a - jp as.opc.noarg - -l13f0h: - call arg.IDX_displcmnt - jr nc,l1413h - ld a,b - rlca - rlca - rlca - add a,046h - cp 076h - jr z,error60 - -l1400h: - ld b,a - call assert_eol - ld (iy+001h),b - ld (iy+002h),c - ld a,(prefix_ixiy) - ld (iy+000h),a - ld c,003h - ret - -l1413h: - call get_char_upper - cp 'I' - jr z,l1426h - cp 'R' - jr nz,l1432h - ld a,b - cp 007h - jr nz,error60 - ld b,05fh - jr l142eh - -l1426h: - ld a,b - cp 007h - jr nz,error60 - ld b,057h -l142eh: - inc de - jp gen.opc.ED2 -l1432h: - cp '(' - jr z,l144ch - call arg.imm_8bit - ld a,b - rlca - rlca - rlca - add a,006h -l143fh: - ld b,a -as.store_2: - call assert_eol - ld (iy+000h),b - ld (iy+001h),l - ld c,002h - ret -l144ch: - inc de - ld a,b - cp 007h - jr nz,error60 - call arg.ww - jr nc,l1466h - cp 030h - jr nc,error60 - add a,00ah - ld b,a - call test_paren_close - jp as.opc.noarg - -error60: - jp error - -l1466h: - call test_expr - call test_paren_close - ld b,03ah - jp as.store_3 - -l1471h: - call assert_comma - call arg.r_HL_A - jr nc,l1483h - cp 006h - jr z,error60 - add a,070h - jp l1400h - -l1483h: - call arg.imm_8bit - call assert_eol - ld a,(prefix_ixiy) - ld (iy+000h),a - ld (iy+001h),036h - ld (iy+002h),c - ld (iy+003h),l - ld c,004h - ret -l149ch: - ld b,a - call assert_comma - ld hl,t_HL.AF - call sub_0318h - jr c,l14c3h - call arg.IX_IY - jr nc,l14cch - ld a,b - cp 030h - jr nz,error6 - ld b,0f9h -l14b4h: - call assert_eol - ld a,(prefix_ixiy) - ld (iy+000h),a - ld (iy+001h),b - ld c,002h - ret - -l14c3h: - ld a,b - cp 030h - jr nz,error6 - ld b,0f9h - jr as.opc.noarg ;14ca - -l14cch: - call get_char_upper - cp '(' - jr nz,l14e8h - inc de - call test_expr - call test_paren_close - ld a,b - cp 020h - jr z,l14e3h - add a,04bh - ld b,a - jp l13c9h - -l14e3h: - ld b,02ah - jp as.store_3 - -l14e8h: - call test_expr - call assert_eol - ld a,001h - add a,b - ld b,a - jp as.store_3 -l14f5h: - call assert_comma - call get_char_upper - cp '(' - jr nz,l1509h - inc de - call test_expr - call test_paren_close - ld b,02ah - jp l1395h - -l1509h: - call test_expr - ld b,021h - jp l1395h - -l1511h: - inc de - call assert_comma - ld b,047h - jr l151fh - -l1519h: - inc de - call assert_comma - ld b,04fh -l151fh: - call get_char_upper - inc de - cp 'A' - jr z,gen.opc.ED2 -error6: - jp ERROR - -l1528h: - cp 020h - jr nc,error6 - add a,002h - ld b,a - call test_paren_close - call assert_comma - call get_char_upper - cp 'A' - jr nz,error6 - inc de -as.opc.noarg: - call assert_eol - ld (iy+000h),b - ld c,001h - ret - -gen.opc.ED2: - call assert_eol - ld (iy+000h),0edh - ld (iy+001h),b - ld c,002h - ret - -as.ADC_SBC: - ld hl,t_HL.AF - call sub_0318h - jr nc,as.AND_CP_OR_SUB_XOR - call assert_comma - call arg.ww - jr nc,error6 - push af - ld a,b - cp 088h - ld b,04ah - jr z,l156ch - ld b,042h -l156ch: - pop af - add a,b -l156eh: - ld b,a - jr gen.opc.ED2 - -as.ADD: - ld hl,t_HL.AF - call sub_0318h - jr c,l159ah - call arg.IX_IY - jr nc,as.AND_CP_OR_SUB_XOR - call assert_comma - ld hl,t_BC.DE.IX.SP - ld a,(prefix_ixiy) - cp 0fdh - jr nz,l158eh - ld hl,t_BC.DE.IY.SP -l158eh: - call arg.reg_16bit - jr nc,error6 - add a,009h -l1596h: - ld b,a - jp l14b4h -l159ah: - call assert_comma - call arg.ww -error61nc: - jr nc,error6 - add a,009h - jp l13ech -as.AND_CP_OR_SUB_XOR: - call get_char_upper - cp 'A' - jr nz,l15b8h - push de - inc de - call next_arg - jr z,l15b7h - pop de - jr l15b8h -l15b7h: - pop af -l15b8h: - call arg.r_HL_A - jr c,l15cbh - call arg.IDX_displcmnt - jr c,l15cfh - call arg.imm_8bit - ld a,b - add a,046h - jp l143fh -l15cbh: - add a,b - jp l13ech -l15cfh: - ld a,b - add a,006h - jp l1400h - -as.SHIFTOP: - call arg.r_HL_A - jr c,l15fah - call arg.IDX_displcmnt - jr nc,error61nc - ld a,b - add a,006h - ld b,a -l15e4h: - call assert_eol - ld a,(prefix_ixiy) - ld (iy+000h),a - ld (iy+001h),0cbh - ld (iy+002h),c - ld (iy+003h),b - ld c,004h - ret - -l15fah: - add a,b -l15fbh: - ld b,a - call assert_eol - ld (iy+001h),b - ld (iy+000h),0cbh - ld c,002h - ret - -as.BITOP: - call arg.bit - call assert_comma - call arg.r_HL_A - jr c,l1624h - call arg.IDX_displcmnt - jr nc,error61nc - ld a,l - rlca - rlca - rlca - add a,006h - add a,b - ld b,a - jr l15e4h -l1624h: - add a,b - ld b,a - ld a,l - rlca - rlca - rlca - add a,b - jr l15fbh - -as.CALL: - push de - call arg.cc_ZCPS - jr nc,l163ch - add a,b - ld b,a - call next_arg - jr z,l163eh - pop de - push de -l163ch: - ld b,0cdh -l163eh: - pop af - call test_expr - jp as.store_3 - -as.RET: - call arg.cc_ZCPS - jr nc,l164eh - add a,b - ld b,a - jr l1650h -l164eh: - ld b,0c9h -l1650h: - jp as.opc.noarg - -as.JP: - push de - call arg.cc_ZCPS - jr c,l1666h -l1659h: - pop de - ld hl,l168ch - call sub_030ah - jr c,l1674h - ld b,0c3h - jr l166eh - -l1666h: - add a,b - ld b,a - call next_arg - jr nz,l1659h - pop af -l166eh: - call test_expr - jp as.store_3 -l1674h: - call assert_eol - ld a,b - and a - jr nz,l1680h - ld b,0e9h - jp as.opc.noarg -l1680h: - ld b,0ddh - dec a - jr z,l1687h - ld b,0fdh -l1687h: - ld l,0e9h - jp as.store_2 - -l168ch: - DC '(HL)' - DC '(IX)' - DC '(IY)' - DB 0 - -as.DJNZ: - call next_arg - ld b,010h - jr l16aeh -as.JR: - call arg.cc_ZC - jr c,l16a9h - ld b,018h - jr l16aeh -l16a9h: - add a,b - ld b,a - call assert_comma -l16aeh: - call arg.j_displ - jp as.store_2 - -as.IM: - call arg.imm_8bit - ld a,l - cp 003h - jr nc,error7 - and a - jr z,l16c7h - ld b,056h - cp 001h - jr z,l16c7h - ld b,05eh -l16c7h: - jp gen.opc.ED2 - -as.RST: - call arg.imm_8bit - ld a,l - push af - add a,b - ld b,a - pop af - and 0c7h - jr nz,error7 - jp as.opc.noarg - -as.POP_PUSH: - call arg.IX_IY - jr c,l16e7h - call arg.zz - jr nc,error7 - add a,b - jp l13ech -l16e7h: - ld a,b - add a,020h - jp l1596h - -as.IN: - call arg.r_HL_A - jr nc,error7 - cp 006h - jr z,error7 - rlca - rlca - rlca - add a,b - ld b,a - cp 078h - jr nz,l170fh - call assert_comma - call sub_171bh - jr c,l1715h - call arg.addr_8bit - ld b,0dbh - jp as.store_2 -l170fh: - call assert_comma - call sub_171bh -l1715h: - jp c,gen.opc.ED2 -error7: - jp ERROR - -sub_171bh: - ld hl,t__C_ - jp sub_0318h - -as.OUT: - call sub_171bh - jr nc,l1739h - call assert_comma - call arg.r_HL_A - jr nc,error7 - cp 006h - jr z,error7 - rlca - rlca - rlca - add a,b - jp l156eh - -l1739h: - call arg.addr_8bit - call assert_comma - cp 'A' - jr nz,error7 - inc de - ld b,0d3h - jp as.store_2 - -as.EX: - ld hl,b_176d_start - call sub_030ah - jr nc,error7 - ld c,b - call assert_eol - ld b,000h - ld hl,l178eh - add hl,bc - add hl,bc - ld a,(hl) - ld (iy+000h),a - ld c,001h - inc hl - ld a,(hl) - and a - ret z - ld (iy+001h),a - ld c,002h - ret - -b_176d_start: - DC 'AF,AF''' -l1773h: - DC 'DE,HL' - DC '(SP),HL' - DC '(SP),IX' - DC '(SP),IY' - db 0 -l178eh: - db 008h,000h - db 0ebh,000h - db 0e3h,000h - db 0ddh,0e3h - db 0fdh,0e3h - -as.DEC_INC: - call arg.IX_IY - jr c,l17b3h - call arg.ww - jr c,l17bfh - call arg.r_HL_A - jr c,l17cch - call arg.IDX_displcmnt - jr nc,error8 - ld a,b - add a,030h - jp l1400h -l17b3h: - ld a,b - ld b,023h - cp 004h - jr z,l17bch - ld b,02bh -l17bch: - jp l14b4h -l17bfh: - push af - ld a,b - ld b,003h - cp 004h - jr z,l17c9h - ld b,00bh -l17c9h: - pop af - jr l17cfh -l17cch: - rlca - rlca - rlca -l17cfh: - add a,b - jp l13ech - -arg.bit: - call arg.imm_8bit - ld a,l - cp 008h - jr nc,error8 - ret - -arg.j_displ: - call test_expr - push bc - push iy - pop bc - and a - sbc hl,bc - dec hl - dec hl - pop bc - call sub_1802h - ld a,h - xor l - bit 7,a - jr nz,error8 - ret - -arg.addr_8bit: - call get_char_upper - cp '(' - jr nz,arg.imm_8bit - inc de - call arg.imm_8bit - jp test_paren_close - -arg.imm_8bit: - call test_expr -sub_1802h: - ld a,h - and a - ret z - inc a - ret z - jr error8 - -test_expr: - push bc - call expr - pop bc - ret nc -error8: - jp ERROR - -arg.zz: - push hl - ld hl,t_BC.DE.HL.AF - jr l181fh - -arg.reg_16bit: - push hl - jr l181fh - -arg.ww: - push hl - ld hl,t_BC.DE.HL.SP -l181fh: - push bc - call sub_030ah - jr nc,l182bh - ld a,b - rlca - rlca - rlca - rlca - scf -l182bh: - pop bc - pop hl - ret - -arg.r_HL_A: - call skipbl - push bc - push hl - ld hl,t_BCDEHL_HL_A - call sub_030ah - ld a,b - pop hl - pop bc - ret - -arg.IX_IY: - push hl - push bc - ld hl,t_IX.IY - call sub_030ah - jr nc,l1852h - ld a,0ddh - dec b - jr nz,l184eh - ld a,0fdh -l184eh: - ld (prefix_ixiy),a - scf -l1852h: + ld de,080h ; DMA_BUF + ld b,d + ld c,e + ldir + call write_sector + ex (sp),hl + ld bc,0ff80h + add hl,bc + ex (sp),hl pop bc - pop hl - ret + jr l11cch -arg.IDX_displcmnt: +write_sector: push hl - push bc - call get_char_upper - cp '(' - jr nz,l18a1h - push de - inc de - ld hl,t_IX.IY - call sub_030ah - jr nc,l18a0h - pop af - ld a,0ddh - dec b - jr nz,l186eh - ld a,0fdh -l186eh: - ld (prefix_ixiy),a - call get_char_upper - cp '+' - jr z,l1882h - cp ')' - ld hl,0 - jr z,l189ah - cp '-' - jr nz,error9 -l1882h: - push af - inc de - call arg.imm_8bit - pop af - cp '+' - jr z,l1894h - ld b,h - ld c,l - ld hl,0 - and a - sbc hl,bc -l1894h: - call get_char_upper - cp ')' - jr nz,error9 -l189ah: - inc de - pop bc - ld c,l - pop hl - scf - ret -l18a0h: - pop de -l18a1h: - pop bc + ld de,dfcb1 + ld c,BDOS_WRITE + call ddtz_bdos pop hl and a - ret + ret z + call close_file +error4: + jp ERROR -arg.cc_ZCPS: - ld hl,t_tstfl_ZCPS - ld c,007h - jr l18b1h +close_file: + ld de,dfcb1 + ld c,BDOS_CLOSE + jp ddtz_bdos -arg.cc_ZC: - ld hl,t_tstfl_ZC - ld c,003h -l18b1h: - push bc - call sub_030ah - ld a,b - pop bc - ret nc - and c - rlca - rlca - rlca - scf - ret +;------------------------------------------------------------------------------- +; > A [startaddr] +; Assemble Zilog Z180 mnemonics -assert_comma: - call next_arg - ret z -error9: - jp ERROR +;cmd_A: -test_paren_close: - call get_char_upper - cp ')' - jr nz,error9 - inc de - ret + +CALL_HL: + jp (hl) + +;------------------------------------------------------------------------------- + + + + +b_176d_start: + DC 'AF,AF''' +l1773h: + DC 'DE,HL' + DC '(SP),HL' + DC '(SP),IX' + DC '(SP),IY' + db 0 + +;------------------------------------------------------------------------------- +; >>L [startaddr] [endaddr] +; List disassembled code cmd_L: - ld hl,cmd_L ld (cmd_rpt),hl call expr jr nc,l18dbh @@ -4461,6 +2964,8 @@ l190fh: jr c,l190fh ret +;------------------------------------------------------------------------------- + cmdl_p_line: push hl call p_disas_line @@ -4473,9 +2978,8 @@ cmdl_p_line: ret p_disas_line: - call p_label call outbl2 - call out.hl.@ + call out_hl call z,outbl call outbl sub a @@ -4487,22 +2991,11 @@ p_disas_line: ld c,15 call p_goto_col - call p_offset - call outbl - jp p_symbol + ; fall thru +;------------------------------------------------------------------------------- + ret -p_offset: - ld de,(var.@) - ld a,d - or e - ret z - call pstr_inl - dc '(@' - and a - sbc hl,de - call out_hl - add hl,de - jp out_rparen +;------------------------------------------------------------------------------- p_disas_instr: sub a @@ -4563,6 +3056,8 @@ l19b1h: scf ret +;------------------------------------------------------------------------------- + disas_pfx.DDFD: inc iy ld hl,b_19ef_start @@ -4589,6 +3084,7 @@ l19edh: and a ret +;------------------------------------------------------------------------------- ; DD/FD 3 byte (ix+d)/(iy+d) b_19ef_start: db 034h @@ -4636,6 +3132,8 @@ l1a0ah: db 0f9h db 0 +;------------------------------------------------------------------------------- + disas_pfx.ED: inc iy ld hl,b_1bc9_start @@ -4656,6 +3154,8 @@ disas_pfx.ED: ld b,4 ret +;------------------------------------------------------------------------------- + disas_pfx.CB: push iy inc iy @@ -4670,6 +3170,8 @@ l1a42h: ld b,2 ret +;------------------------------------------------------------------------------- + disas_nopfx: ld hl,b_1b54_start call lookup_opc @@ -4689,6 +3191,8 @@ disas_nopfx: ld b,3 ret +;------------------------------------------------------------------------------- + sub_1a72h: ld a,(hl) cp 0ffh @@ -4744,6 +3248,7 @@ get_mnemonic: scf ret +;------------------------------------------------------------------------------- ; 1 byte opcodes (no parameters) ; Format: db opcode, t_MNEMONICS-index b_1ab6_start: @@ -4997,6 +3502,8 @@ b_1c55_start: dw p_arg_bitop db 0 +;------------------------------------------------------------------------------- + p_arg_r_r: call p_arg_r call p_char_comma @@ -5059,8 +3566,7 @@ l1ce5h: sub_1ce8h: call p_char_lparen call p_arg_ww -out_rparen: - jp p_char_rparen + jr out_rparen l1cf5h: call p_A_comma @@ -5100,7 +3606,11 @@ l1d29h: sub_1d2ch: call p_char_lparen ld a,(iy+001h) - jp l1e6bh +p_arg_nn_rp: + call out_hex +out_rparen: + jr p_char_rparen + l1d37h: call sub_1d2ch jr p_char_comma_A @@ -5137,27 +3647,30 @@ p_arg_addr_a: call p_arg_addr p_char_comma_A: call p_char_comma + jr p_char_A + +p_A_comma: + call p_char_A +p_char_comma: + ld a,',' + db 021h p_char_A: ld a,'A' - jr outchar1 -p_arg_a_addr: - call p_A_comma - jp p_arg_addr + db 021h l1d85h: ld a,'0' - jr outchar1 + db 021h l1d89h: ld a,'1' - jr outchar1 + db 021h l1d8dh: ld a,'2' - jr outchar1 - -p_A_comma: - call p_char_A -p_char_comma: - ld a,',' -outchar1: + db 021h +p_char_rparen: + ld a,')' + db 021h +p_char_lparen: + ld a,'(' jp outchar l1d92h: @@ -5210,6 +3723,16 @@ p_arg_ww_addr: call p_char_comma jr p_arg_addr +p_arg_a_addr: + call p_A_comma +p_arg_addr: + call p_char_lparen + ld l,(iy+001h) + ld h,(iy+002h) + ld a,001h + call sub_1d50h + jr p_char_rparen + p_arg_bitop: ld a,(isprefix_ixiy) and a @@ -5241,17 +3764,6 @@ l1e0eh: l1e11h: jr p_arg_r0 -p_arg_addr: - call p_char_lparen - ld l,(iy+001h) - ld h,(iy+002h) - ld a,001h - call sub_1d50h - -p_char_rparen: - ld a,')' - jp outchar - p_arg_r: ld a,(iy+000h) rra @@ -5276,20 +3788,18 @@ p_arg_r0: l1e4dh: call pstr ld a,(iy+001h) - and a - jp m,l1e61h - call pstr_inl - dc '+' - ld a,(iy+001h) - jr l1e6bh -l1e61h: - call pstr_inl - dc '-' - ld a,(iy+001h) + push af + rlca + ld a,'+' + jr nc,l1e61h + pop af neg -l1e6bh: - call out_hex - jr p_char_rparen + push af + ld a,'-' +l1e61h: + call outchar + pop af + jp p_arg_nn_rp p_arg_r1: ld hl,t_BCDEHL_HL_A @@ -5333,6 +3843,8 @@ p_arg: call sel_dc_string jp pstr +;------------------------------------------------------------------------------- + t_MNEMONICS: DC 'ADC' DC 'ADD' @@ -5432,38 +3944,16 @@ t_BC.DE.HL.SP: 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' @@ -5484,7 +3974,9 @@ t__C_: DC '(C)' DB 0 -sub_1ffeh: +;------------------------------------------------------------------------------- + +tc_set_bp: ld hl,(reg.pc) ld a,h or l @@ -5501,7 +3993,7 @@ sub_1ffeh: ld b,0 ld hl,(reg.pc) add hl,bc - call sub_09cah + call bp_trace_enter ld iy,(reg.pc) ld hl,b_2039_start call lookup_opc @@ -5510,11 +4002,13 @@ sub_1ffeh: ex de,hl l2031h: call CALL_HL - call c,sub_09cah + call c,bp_trace_enter l2037h: scf ret +;------------------------------------------------------------------------------- + b_2039_start: db 0ffh,0ddh,000h ;Prefix DD dw l20a7h @@ -5534,20 +4028,22 @@ b_2048_start: dw l20dch db 0ffh,0cfh,000h ;rst 8 dw l2115h - db 0c7h,0c7h,000h ; + db 0c7h,0c7h,000h ;rst n dw l20f9h - db 0c7h,0c4h,000h ; + db 0c7h,0c4h,000h ;call cc,mn dw l2080h - db 0f7h,010h,000h ; + db 0f7h,010h,000h ;djnz d; jr d dw l2093h - db 0e7h,020h,000h ; + db 0e7h,020h,000h ;jr cc,d dw l2093h - db 0c7h,0c2h,000h ; + db 0c7h,0c2h,000h ;jp cc,mn dw l208bh - db 0c7h,0c0h,000h ; + db 0c7h,0c0h,000h ;ret cc dw l20c5h db 0 +;------------------------------------------------------------------------------- +; call mn call cc,mn l2080h: ld a,(b_21e2_start) and a @@ -5555,11 +4051,14 @@ l2080h: ld a,(trace_call_flag) and a ret nz + +; jp mn jp cc,mn l208bh: ld l,(iy+001h) ld h,(iy+002h) scf ret + l2093h: ld c,(iy+001h) ld a,c @@ -5572,27 +4071,34 @@ l2093h: 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,(iy+001h) - cp 0e9h + cp 0e9h ; jp (ix); jp (iy) scf ret z and a ret + +; Prefix ED l20b8h: ld a,(iy+001h) - cp 04dh + cp 04dh ; reti jr z,l20dch - cp 045h + cp 045h ; retn jr z,l20dch and a ret @@ -5629,7 +4135,8 @@ l20edh: inc hl ld d,(hl) ex de,hl - call sub_09cah + call bp_trace_enter +l2115h: and a ret @@ -5650,42 +4157,51 @@ l20f9h: l2113h: scf ret -l2115h: - and a - ret + +;------------------------------------------------------------------------------- +; >>C[N][J] [steps] +; >>C[N][J] W expression +; >>C[N][J] U expression +; trace over Calls [No list] [Jumps only] /.While./.Until. + cmd_C: - ld hl,cmd_C ld a,1 - jr l2122h + jr cmd_tc + +;------------------------------------------------------------------------------- +; >>T[N][J] [steps] +; >>T[N][J] W expression +; >>T[N][J] U expression +; Trace [no List] [Jumps only] / .While. / .Until. + cmd_T: xor a - ld hl,cmd_T -l2122h: +cmd_tc: ld (cmd_rpt),hl ld (trace_call_flag),a call get_char_upper sub 'N' - jr nz,l212eh + jr nz,tc_non inc de -l212eh: +tc_non: ld (trace_N_flag),a call get_char_upper sub 'J' - jr nz,l2137h + jr nz,tc_noj inc de -l2137h: +tc_noj: ld (trace_J_flag),a - call sub_21a6h - jr z,l2145h - ld hl,1 + call tc_chk_u_or_w + jr z,tc_save_uw_expr_ptr + ld hl,1 ;default: 1 step call get_lastarg_def -l2145h: - ld (trace_count),hl +tc_save_uw_expr_ptr: + ld (trace_cnt_or_ptr),hl sub a - ld (l0941h),a + ld (bp_p_cpu_flag),a l214ch: - call sub_1ffeh - jr l21a3h + call tc_set_bp + jr user_go1 l2151h: call bp_clr_temporary @@ -5699,40 +4215,41 @@ l2151h: call lookup_opc jr nc,l214ch l216bh: - ld a,(trace_UW_flag) + ld a,(trace_UW_flag) ;0 or 'U' or 'W' and a - jr z,l2188h - ld de,(trace_count) + jr z,tc_cnt ;flag is 0, check for step count. + ld de,(trace_cnt_or_ptr) call expr ld a,h or l add a,0ffh sbc a,a - ld hl,trace_UW_flag + ld hl,trace_UW_flag ;'U' or 'W' xor (hl) - bit 1,a + bit 1,a ;'U' = 55H, 'W' = 57H jr z,l2193h -l2185h: - jp l0902h -l2188h: - ld hl,(trace_count) +do_break0: ;print registers and go to main loop + jp do_break + +tc_cnt: + ld hl,(trace_cnt_or_ptr) dec hl - ld (trace_count),hl + ld (trace_cnt_or_ptr),hl ld a,h or l - jr z,l2185h + jr z,do_break0 l2193h: - call sub_1ffeh - jr nc,l2185h + call tc_set_bp + jr nc,do_break0 ld a,(trace_N_flag) ld b,a - ld a,(l0941h) + ld a,(bp_p_cpu_flag) or b - ld (l0941h),a -l21a3h: + ld (bp_p_cpu_flag),a +user_go1: jp user_go -sub_21a6h: +tc_chk_u_or_w: call skipbl xor a ld (trace_UW_flag),a @@ -5770,25 +4287,27 @@ l21dah: cp 045h ret +;------------------------------------------------------------------------------- + +con_col: + db 0 + +;------------------------------------------------------------------------------- + b_21e2_start: db 0 trace_call_flag: db 0 ;1=call, 0=trace trace_UW_flag: db 0 ;0 or 'U' or 'W' -trace_count: +trace_cnt_or_ptr: dw 0 trace_N_flag: db 0 ;0 if 'N' trace_J_flag: db 0 ;0 if 'J' -;------------------------------------------------------------------------------- - -con_col: - db 0 - -l0941h: +bp_p_cpu_flag: db 0 bp_tab: @@ -5800,8 +4319,6 @@ bp_tab: expr_p1: dw expr_buf -expr_p2: - dw expr_buf expr_buf: current_cseg defl $ - current_cseg @@ -5888,12 +4405,7 @@ current_cseg defl $ ds EXPR_BUF_SIZE - ($ - expr_buf) expr_bufe: -msg_Y: - dc 'Yn' -reg_Y: - rept YREG_CNT - dw 0 - endm +;------------------------------------------------------------------------------- last_S: dw TPA @@ -5920,16 +4432,6 @@ high_load: max_load: dw TPA -l1262h: - dw 0 -last_A: - dw TPA -cmd_A_prev: - dw TPA - -prefix_ixiy: - db 0 - isprefix_ixiy: db 0 last_L: @@ -5939,12 +4441,11 @@ disas_arg_16: disas_argtype: db 0 -symlen_max: ;max length of symbols read so far - db 0 +pbl_loop_adr: + dw 0 + cur_fcb: dw 0 -fcbsym: - ds 33 ddtz_size equ $-ddtz_base ddtz_end: