X-Git-Url: http://cloudbase.mooo.com/gitweb/ddt180.git/blobdiff_plain/201101b35cfea603248f7e89c571b4653b8c663e..fb2242116670a4c60e8ace16df4bfb8c9ffc5a27:/ddt180.z80?ds=sidebyside diff --git a/ddt180.z80 b/ddt180.z80 index 28b0199..fd16076 100644 --- a/ddt180.z80 +++ b/ddt180.z80 @@ -6,26 +6,8 @@ ; - 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. -;------------------------------------------------------------------------------- -; Relocation loader -; -TPA equ 0100h - cseg - .phase TPA - - jp start - ds 3 -ldr_end: -ldr_size equ $ - TPA -current_phase defl $ - - .dephase -current_cseg defl $ - -;------------------------------------------------------------------------------- -; DDT/Z core -; + maclib config.inc ; Some greneral definitions @@ -41,147 +23,490 @@ CNTRX equ 'X'-'@' BDOS equ 5 TPA equ 0100h -; BDOS function calls - -BDOS_PSTR equ 9 ;Print String - ; ddtz specific definitions 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 4 ;Size of a breakpoint record +bitmap_size equ (prog_size+7)/8 + ;------------------------------------------------------------------------------- + cseg +start: ddtz_base: - jp ddtz_bdos + jr reloc + nop l0003h: - rst 30h -di_or_ei: + rst 30h ;rst used by ddtz +di_or_ei: ;ints enabled/disabled while ddtz is running nop ret -ddtz_bdos: - jp 0 -current_cseg defl $ - current_cseg - .phase current_phase + current_cseg +;------------------------------------------------------------------------------- + signon: db 'DDTZ/180' db ' - Version ' maclib version.inc defvers - db CR,LF,'$' -msgz80: - db 'Z80 or better required!',cr,lf,'$' - -current_phase defl $ - .dephase -current_cseg defl $ - ds STACK_SIZE - (current_phase - signon) + dc ' (' +;------------------------------------------------------------------------------- -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 +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 -conbuf: - db CONBUF_SIZE +cmde_clr: + ld (hl),0 + inc hl + dec bc + ld a,b + or c + jr nz,cmde_clr - ld sp,stack +; Determine current position + +reloc: + ld bc,(028h-2) + ld de,(028h) + ld a,i ;get iff2 + ex af,af' + di + ld sp,028h ;rst instr needs a minimal stack + ld hl,0e9e1h ;opcpdes pop hl/jp (hl) + ld (028h),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 de,ddtz_base - call cp_hl_de - jr c,l0079h - ex de,hl -l0079h: - ld de,TPA -l007ch: - dec hl - ld (hl),000h - ld a,h - sub d - ld b,a - ld a,l - sub e - or b - jr nz,l007ch - ld a,i - ld (reg.i),a - ld a,0f3h - jp po,l0093h - ld a,0fbh -l0093h: - ld (reg.iff),a - call di_or_ei - ld hl,ddtz_base - ld l,000h - ld (reg_sp),hl - ld hl,(1) ;wboot addr - ld de,?const - ld b,6 -vini_l: - inc hl - inc hl + 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 - ex de,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 + + xor a + call cinit + ld a,1 + 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 z180reg.inc + +iobyte equ 3 + +max_device equ 3 + +;------------------------------------------------------------------------------- + +; init device +cinit: ; a = device + call vector_io_0 + dw as0init + dw rret + dw rret + dw rret + +; character input status +const: ; return a != 0 if character waiting + call vector_io + dw as0ista + dw null$status + dw csio_ista + dw null$status + +; character input +conin: ; return a = input char + call vector_io + dw as0inp + dw null$input + dw csio_inp + dw null$input + +; character output +conout: ; c = output char + call vector_io + dw as0out + dw rret + dw csio_out + dw rret + +;------------------------------------------------------------------------------- + +vector_io: + ld a,(iobyte) +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) + +;------------------------------------------------------------------------------- + +null$input: + ld a,1Ah +rret: + ret +ret$true: + or 0FFh + ret + +null$status: + xor a + ret - jr mainloop +;------------------------------------------------------------------------------- +; +; TC = (f PHI /(2*baudrate*Clock_mode)) - 2 +; +; TC = (f PHI / (32 * baudrate)) - 2 +; +; Init Serial I/O for console input and output (ASCI1) +; + + + +as0init: + ld hl,initab0 + jp ioiniml + +as1init: + ld hl,initab1 + jp ioiniml + + + ld a,M_MPBT + out0 (cntlb1),a + ld a,M_RE + M_TE + M_MOD2 ;Rx/Tx enable + out0 (cntla1),a + ld a,M_RIE + out0 (stat1),a ;Enable rx interrupts + + ret ; + + +initab0: + db 1,stat0,0 ;Disable rx/tx interrupts + ;Enable baud rate generator + db 1,asext0,M_BRGMOD+M_DCD0DIS+M_CTS0DIS + db 2,astc0l,low 28, high 28 + db 1,cntlb0,M_MPBT ;No MP Mode, X16 + db 1,cntla0,M_RE+M_TE+M_MOD2 ;Rx/Tx enable, 8N1 + db 0 + +initab1: + db 1,stat1,0 ;Disable rx/tx ints, disable CTS1 + db 1,asext1,M_BRGMOD ;Enable baud rate generator + db 2,astc1l,low 3, high 3 + db 1,cntlb1,M_MPBT ;No MP Mode, X16 + db 1,cntla1,M_RE+M_TE+M_MOD2 ;Rx/Tx enable, 8N1 + db 0 + +;------------------------------------------------------------------------------- + +ioiniml: + push bc + xor a +ioml_lp: + ld b,(hl) + inc hl + cp b + jr z,ioml_e + + ld c,(hl) + inc hl + otimr + jr ioml_lp +ioml_e: + pop bc + ret + +;------------------------------------------------------------------------------- + +as0ista: + in0 a,(stat0) + rlca + sbc a,a + ret + +as1ista: + in0 a,(stat1) + rlca + sbc a,a + ret + +as0inp: + in0 a,(stat0) + rlca + jr nc,as0inp + in0 a,rdr0 + ret - ds CONBUF_SIZE + 3 - ($ - conbuf) +as1inp: + in0 a,(stat1) + rlca + jr nc,as1inp + in0 a,rdr1 + ret + +as0out: + in0 a,(stat0) + and M_TDRE + jr z,as0out + out0 (tdr0),c + ld a,c + ret + +as1out: + in0 a,(stat1) + and M_TDRE + jr z,as1out + out0 (tdr1),c + ld a,c + ret ;------------------------------------------------------------------------------- -?const: jp 0 ; return console input status -?conin: jp 0 ; return console input character -?cono: jp 0 ; send console output character -?list: jp 0 ; send list output character -?auxo: jp 0 ; send auxiliary output character -?auxi: jp 0 ; return auxiliary input character + +csio_rx_tmp: db 0ffh + +csio_ista: + ld hl,csio_rx_tmp + ld a,(hl) + cp 0ffh + jr nz,csist_1 + ld a,01 + call csio_wr + call csio_rd + call csio_rd + ld (hl),a + sub a,0ffh + ret z +csist_1: + or 0ffh + ret + +csio_inp: + ld hl,csio_rx_tmp + ld a,(hl) + ld (hl),0ffh + cp 0ffh + ret nz +csin_1: + ld a,01 + call csio_wr + call csio_rd + call csio_rd + cp 0ffh + jr z,csin_1 + ret + +csio_rd: + ld a,M_CSIO_RE + call csio_cmd_wait + in0 a,(trdr) + ret + +csio_out: + ld a,02 + call csio_wr + call csio_rd + call csio_rd + or a + jr z,csio_out + + ld a,c + inc a ;ff..02 --> 00..03 + cp 04h + jr nc,csout_1 + ld a,00h + call csio_wr +csout_1: + ld a,c +csio_wr: + out0 (trdr),a + ld a,M_CSIO_TE +csio_cmd_wait: + out0 (cntr),a +cswr_wait: + in0 a,(cntr) + and M_CSIO_TE+M_CSIO_RE + jr nz,cswr_wait + ret + + endif ; CPM + +;------------------------------------------------------------------------------- CMDTAB: - dw ERROR ;cmd_@ ;examine/substitute the displacement register @ - dw ERROR ;cmd_A ;Assemble +; 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 ERROR ; + 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 @@ -227,7 +552,7 @@ mainloop: push hl ld (cmd_rpt),hl inc de - sub '@' + sub 'B' jr c,ERROR cp 'Z'+1-'@' jr nc,ERROR @@ -255,8 +580,7 @@ crlf: sub_01d9h: call pstr_inl dc '-' - dec hl - jp cpl.hl + jp neg.hl out_hl_dec_neg: push hl @@ -323,9 +647,8 @@ out.bin.b: l01c9h: rlca push af - ld a,'0'/2 - adc a,a - call outchar + and 1 + call out_dgt pop af djnz l01c9h ld a,'"' @@ -376,7 +699,7 @@ outchar: push af and 07fh ld c,a - call ?cono + call conout ld hl,con_col inc (hl) pop af @@ -409,10 +732,10 @@ inchar: push hl push de push bc - call ?const + call const and a jr z,inch1 - call ?conin + call conin scf inch1: pop bc @@ -430,7 +753,6 @@ DELC: call DELC1 dec hl dec b - inc c ld a,(hl) cp ' ' ret nc @@ -451,13 +773,10 @@ DELL: get_line: push hl ; ld hl,conbuf ; - ld c,(hl) ; - inc hl ; - ld b,000h ; - inc hl ; + ld b,0 ; inlnxtch: - ld a,c ; - or a ; + ld a,b ; + cp CONBUF_SIZE ; jr z,inl_e ; call incharw ; cp CR ; @@ -493,16 +812,12 @@ gl_5: call outchar ; inc hl ; inc b ; - dec c ; jr inlnxtch ; inl_e: ld (hl),0 - ld hl,conbuf+1 ; - ld (hl),b ; call CRLF ; - inc hl - ex de,hl + ld de,conbuf ; pop hl ; ret ; @@ -657,12 +972,12 @@ l0348h: ret m jr l0348h -sub_034eh: +get_arg_range_target: call get_arg_range push hl push bc call next_arg - call sub_0363h + call get_arg_final ex de,hl pop bc pop hl @@ -673,7 +988,7 @@ sub_035dh: jr c,error0 ret -sub_0363h: +get_arg_final: call sub_035dh l0366h: jp assert_eol @@ -937,6 +1252,9 @@ do_factor: ld hl,TPA cp 'L' ret z + ld hl,(reg.pc) + cp '$' + ret z cp '-' jr z,fact_factneg cp '~' @@ -995,8 +1313,13 @@ fact_reg.CPU: ld h,000h ret +fact_factinv: + call fact_factor + jr cpl.hl + fact_factneg: call fact_factor +neg.hl: dec hl cpl.hl: ld a,h @@ -1007,10 +1330,6 @@ cpl.hl: ld l,a ret -fact_factinv: - call fact_factor - jr cpl.hl - fact_mem: call expr1 jr c,error1 @@ -1288,6 +1607,56 @@ b_0709_start: 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] @@ -1677,7 +2046,7 @@ cmd_X: call get_line call skipbl jr z,l0c30h - call sub_0363h + call get_arg_final ex de,hl pop bc pop hl @@ -1949,11 +2318,11 @@ cmd_O: ret ;------------------------------------------------------------------------------- -; > Vstartaddr endaddr targetaddr +; > V startaddr endaddr targetaddr ; Verify (compare) two memory areas cmd_V: - call sub_034eh + call get_arg_range_target l0dedh: push bc ld a,(de) @@ -1985,7 +2354,7 @@ l0e10h: ; Move memory cmd_M: - call sub_034eh + call get_arg_range_target call cp_hl_de jr nc,cmdm_up add hl,bc @@ -1995,7 +2364,7 @@ cmd_M: dec hl dec de lddr - db 01h ;swallow ldir instruction (ld bc,...) + ret cmdm_up: ldir ret @@ -2094,9 +2463,9 @@ l0ed3h: ret sub_0ee6h: - ld hl,conbuf+1 + ld hl,conbuf call sub_0ef7h - ld de,conbuf+1 + ld de,conbuf and a sbc hl,de ld b,l @@ -2307,12 +2676,14 @@ i.getchar: i.storebyte: push af push de - ld de,TPA ;lowest allowed load address + ld de,ddtz_base ;don't load over ddtz call cp_hl_de - jr c,error2 - ld de,(BDOS+1) ;highest allowed load address + 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 @@ -2493,13 +2864,22 @@ disas_nopfx: disas_pfx.ED: inc iy + ld hl,l228bh + call lookup_op_arg + ld b,3 + ret c + ld hl,b_1c40_start + call lookup_op_arg + ld b,4 + ret c + ld hl,b_1bc9_start ;1 byte opcode, no arguments call lookup_op - ld b,2 - ret c + jr c,da_ed1 + ld hl,b_1bf4_start call lookup_op_arg - jr nc,da_ed1 + ret nc ld a,e cp a_noarg @@ -2515,16 +2895,8 @@ disas_pfx.ED: da_ed0: scf - ld b,2 - ret da_ed1: - ld hl,l228bh - call lookup_op_arg - ld b,3 - ret c - ld hl,b_1c40_start - call lookup_op_arg - ld b,4 + ld b,2 ret ;------------------------------------------------------------------------------- @@ -2621,6 +2993,16 @@ l1a0ah: ;------------------------------------------------------------------------------- +test_DDFD: + ld a,(hl) + and a + ret z + inc hl + cp (iy+000h) + jr nz,test_DDFD + scf + ret + lookup_op: ld a,(hl) inc hl @@ -2635,38 +3017,15 @@ l1a7fh: ld e,a_noarg jr get_mnemonic - -test_DDFD: - ld a,(hl) - and a - ret z - inc hl - cp (iy+000h) - jr nz,test_DDFD - scf - ret - lookup_op_arg: - ld a,(iy+000h) - and (hl) - inc hl - cp (hl) - inc hl - jr z,l1aa8h - inc hl - inc hl - ld a,(hl) - and a - jr nz,lookup_op_arg - ret - -l1aa8h: - ld b,(hl) - inc b + call lookup_branch_op + ret nc + ld a,e + ld e,d + cp a,0ffh ret z ;carry clear - dec b - inc hl - ld e,(hl) + ld b,a + get_mnemonic: ld hl,t_MNEMONICS bit 7,b @@ -2686,18 +3045,17 @@ get_m1: ret lookup_branch_op ;TODO - ld a,(iy+000h) - and (hl) + ld a,(hl) + and a + ret z inc hl + and (iy+000h) cp (hl) inc hl jr z,l1aa8_br inc hl inc hl - ld a,(hl) - and a - jr nz,lookup_branch_op - ret + jr lookup_branch_op l1aa8_br: ld e,(hl) @@ -3008,8 +3366,8 @@ a_rr equ $-t_argf db fi_ry,',' ;ld r[y],r[z] a_r equ $-t_argf db fi_rz,0 ;op r[z] -a_ar equ $-t_argf - db 'A,',fi_rz,0 ;op A,r[z] +;a_ar equ $-t_argf +; db 'A,',fi_rz,0 ;op A,r[z] a_cc equ $-t_argf db fi_ccy,0 ;op cc[y] a_rst equ $-t_argf @@ -3282,25 +3640,13 @@ pstr_inl: opc macro x i_&x equ opc_index -o_&x equ $-opc_tabstart +;o_&x equ $-opc_tabstart dc '&x' opc_index defl opc_index+1 endm -opc1 macro x,y - -i_&x&y equ opc_index -o_&x&y equ $-opc_tabstart - db '&x' -i_&y equ opc_index+1 -o_&y equ $-opc_tabstart - dc '&y' -opc_index defl opc_index+2 - endm - - t_MNEMONICS: -opc_tabstart defl $ +;opc_tabstart defl $ opc_index defl 0 ; 1-byte other opc NOP @@ -3363,8 +3709,7 @@ opc_index defl 0 opc RRD opc RLD -;Block instructions -t_mn_bli: +; Block instructions opc LDI opc CPI opc INI @@ -3382,7 +3727,7 @@ t_mn_bli: opc INDR opc OTDR -;Z180 +; Z180 opc IN0 opc OUT0 opc TST @@ -3488,7 +3833,7 @@ t_op_branch: dw l20ach db 0ffh,0edh ;Prefix ED dw l20b8h -t_op_branch0: + db 0ffh,0cdh ;call mn dw l2080h db 0ffh,0c3h ;jp mn @@ -3671,91 +4016,6 @@ bp_tab: endm endm -expr_buf: -current_cseg defl $ - current_cseg - .phase current_phase + current_cseg - -start: - LD SP,ldr_end+(stack-ddtz_base) - LD DE,signon ;ldr_end+(expr_buf-ddtz_base) - LD C,BDOS_PSTR - CALL BDOS - - xor a - dec a - jp po,reloc - ld de,msgz80 - LD C,BDOS_PSTR - CALL BDOS - jp 0 - -reloc: - LD HL,ldr_end+ddtz_size ;start of reloc bitmap - ld bc,0108h ;init bit counter - - EXX - LD HL,(BDOS+1) - LD (ldr_end+(ddtz_bdos+1-ddtz_base)),HL - LD BC,ddtz_size-1 - LD D,B - LD E,0FFH - INC DE ;size rounded up to next page boundary - INC BC ;ddtz_size - OR A - SBC HL,DE ;BDOS - size - LD (BDOS+1),HL ;-> new BDOS entry - - push hl - PUSH BC - ld de,ldr_end - sbc hl,de - EX DE,HL ;-> DE - LD HL,ldr_size - add hl,bc - ld b,h - ld c,l - LD HL,TPA -reloc_lp: - EXX - djnz reloc_nl - ld b,c ;reload bit counter - LD e,(HL) ;get next 8 relocation bits - INC HL -reloc_nl: - sla e - EXX - JR NC,reloc_next - DEC HL - LD A,(HL) - ADD A,E - LD (HL),A - INC HL - LD A,(HL) - ADC A,D - LD (HL),A -reloc_next: - cpi - jp pe,reloc_lp - dec hl - - POP BC - pop de - EX DE,HL - ADD HL,BC - EX DE,HL - DEC DE - LDDR - LD HL,conbuf+2-ddtz_base - ADD HL,DE - JP (HL) - -current_phase defl $ - .dephase -current_cseg defl $ - - ds EXPR_BUF_SIZE - ($ - expr_buf) -expr_bufe: - ;------------------------------------------------------------------------------- last_S: @@ -3783,9 +4043,54 @@ last_L: dw TPA pbl_loop_adr: + dw 0addeh + +bitmap_end: dw 0 +;------------------------------------------------------------------------------- + +conbuf: + ds CONBUF_SIZE+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: ;-------------------------------------------------------------------------------