home *** CD-ROM | disk | FTP | other *** search
Text File | 1990-07-22 | 19.1 KB | 1,082 lines |
- ;
- ;JMON-monitor for banked BIOS
- ;
- ;Vers Date Name Notes
- ;1.00 88Jan22 Loke J Release of MicroBee version for ZASM
- ; Pages switched in banks of 56k (0000h-DFFFh)
- ; Bank switching using port 0Ah
- ; out (0Ah),a ;A=bank 0..3
- ; Common memory 0E000h-0FFFFh
- ; My version uses RAM at 0F800h for this program
- ; with self-modifying code.
- ; ZASM has no PHASE directive, so I had to use
- ; an offset for EVERY absolute reference. e.g.
- ; (and no laughing)
- ; ld sp,stk+poff ;+poff offset
- ; When writing the JVDU.Z80 and the JKBDST.Z80
- ; overlays be sure to use +poff in the same
- ; manner.
- ;0.32 88Jan15 Loke J Fixed Sxxxx stepping bug
- ;0.31 88Jan07 Loke J Added Hxxxx,yyyy option, Z display option
- ; increased some constants to take more room
- ; more $0 to $7, changed dispr and reg to make
- ; use of regtbl. Added .R and .A option to prsadr
- ; Added command list in comments below
- ;0.30 88Jan05 Loke J Added code for bootstrap loader from
- ; CP/M TPA, patch loading code
- ; Revised register display, and prsadr
- ; Added Qxxxx option, changed $0 to $7
- ; Added S,$$$ option
- ;0.20 87Aug28 Loke J Merged KBD.Z80, fixed reverse-order
- ; breakpoint resetting
- ;0.10 87Jul25 Loke J Original version, uses include KBD.Z80
- ; Uses a hardware scroll VDU driver
- ;
- ;Commands
- ; B display all breakpoints
- ; Bxxxx toggle breakpoint at xxxx
- ;
- ; C clear all breakpoints
- ;
- ; D dump 128 bytes from current pointer
- ; Dxxxx dump 128 bytes from xxxx
- ; Dxxxx,yyyy dump from xxxx to yyyy
- ; D,yyyy dump from last addr to yyyy
- ;
- ; Fxxxx,yyyy fill from xxxx to yyyy with 00
- ; Fxxxx,yyyy,nn fill from xxxx to yyyy with nn
- ;
- ; G go to PC
- ; Gxxxx go to xxxx
- ; Gxxxx,yyyy go to PC, temporary breakpoint at yyyy
- ;
- ; Hxxxx,yyyy display sum and difference (hexadecimal)
- ;
- ; Inn input from port nn
- ; Inn,oo input from port nn, put oo on A8..A15
- ;
- ; Mxxxx,yyyy,zzzz move memory from xxxx..yyyy to zzzz
- ;
- ; Onn,oo output value oo to port nn
- ;
- ; Q quit to ROM monitor
- ; Qxxxx quit to address xxxx
- ;
- ; R display registers
- ; Rrxxxx set register r to xxxxx, where r in [ABDHXYSPZ]
- ; RFfff set flag(s) f in flag register, f in [SZHPNC]
- ;
- ; S substitute memory contents from last address
- ; Sxxxx substitute memory contents at xxxx
- ;
- ; Z display current PAGE register
- ; Zxxxx set PAGE register to xxxx
- ;
- ;notes
- ; field description example notes
- ;
- ; nn hex number I0 input from port 00h
- ;
- ; xxxx hex number G,0DF3 go with temp brkpt at 0DF3h
- ; or PC spec D. dump from PC onwards
- ; or PC relative target B.r brkpt assuming PC at JR
- ; or PC absolute target B.a brkpt e.g. with PC at CALL
- ;
- ; rr register name RA38 set A to 38h
- ; RH1234 set HL to 1234h
- ;
- ; ffff flag name RFZPS set FLAGS Z P and S
- ;
- ;Constants
- ;
- buflen equ 16 ;size of input buffer
- maxbrk equ 8 ;max number of breakpoints
- stklvl equ 16 ;stack size
- brkval equ 0FFh ;opcode for break
- brkadr equ 0038h ;location for RST
- rommon equ 0E003h ;Entry point for ROM monitor
- pdest equ 0F800h
- ;
- ;
- org 0100h
- jp cboot
- db 13,'JMON monitor for banked BIOS',13,10,26
- cboot: ld a,(005Ch+8+1) ;look at TYPE byte
- cp ' ' ;which PCG/Colour bank
- ld a,40h ;switch for Colour bank
- jr z,cboot1
- xor a ;switch for PCG bank
- cboot1: out (08h),a
- ld hl,patbas
- ld de,pdest
- ld bc,pattop-patbas
- ldir
- ld a,(005Ch+1)
- cp ' ' ;execute?
- ret z
- jp pdest
- ;
- ;
- ;
- org 0180h
- patbas equ $
- poff equ pdest-patbas
- ;
- ;Entry vector
- jmon: jp poff+boot
- ;
- ;
- ;Re-entry trap to monitor
- trap: nop
- nop
- ;Store registers
- ld (xhl+poff),hl
- ld (xde+poff),de
- ld (xbc+poff),bc
- ld (xix+poff),ix
- ld (xiy+poff),iy
- pop hl
- dec hl
- ld (xpc+poff),hl
- ld (xsp+poff),sp
- ld sp,stk+poff
- push af
- pop hl
- ld (xaf+poff),hl
- ;Calculate & store active page
- ld a,(brkadr+1)
- sub a,0+((trap+poff) and 255)
- ld (xz+poff),a
- ;Restore restart bytes
- ld hl,brkadr
- ld de,poff+xrst
- ld b,3 ;For each of 3 bytes
- tp1: xor a
- ld c,a ;C=A=0
- tp2: out (0Ah),a
- ld a,(de)
- ld (hl),a
- inc de
- inc c
- ld a,c
- cp 3 ;Loop for each of 3 pages
- jr c,tp2
- inc hl
- djnz tp1
- ;Restore breakpoint bytes
- ld hl,nbrk+poff
- ld a,(hl) ;A=no of breakpoints
- inc hl
- ld b,a ;B=A
- add a,a
- jr z,tp4 ;skip if no breakpoints
- add a,a ;A*=4 bytes for each breakpoint
- call poff+addhla ;HL+=A
- tp3: dec hl
- ld c,(hl) ;C=old byte
- dec hl
- ld d,(hl)
- dec hl
- ld e,(hl) ;DE=address
- dec hl
- ld a,(hl) ;A=page
- out (0Ah),a
- ld a,c
- ld (de),a ;restore old byte
- djnz tp3
- tp4:
- ;Restore temporary breakpoint if applicable
- trppat equ $+1
- jr tp6
- gbkpag equ $+1
- tp5: ld a,00h
- out (0Ah),a
- gbkint equ $+1
- ld a,00h
- gbkadr equ $+1
- ld (0000h),a
- tp6:
- trpskp equ tp6-tp5
- ;
- ;Display registers
- disp:
- ;Display flags register
- ld a,(poff+xaf)
- ld c,a ;C=flags
- ld b,8 ;8 flags
- ld hl,flnam+poff ;HL=>flag names
- dsp1: ld a,' '
- rl c
- jr nc,dsp2
- ld a,(hl)
- dsp2: call poff+wr$a
- inc hl
- djnz dsp1
- ;Display A, B,D,H,X,Y, Z, S,P
- call poff+wrsppc ;A
- db 'A','='+80h
- ld a,(poff+xaf+1)
- call poff+wra8
-
- ld hl,poff+regtbl
- ld b,5
- dsp3: call poff+dspr ;B,D,H,X,Y
- djnz dsp3
-
- call poff+wrsppc
- db 'Z','='+80h
- ld a,(poff+xz)
- call poff+wra8
-
- call poff+dspr ;S
- call poff+dspr ;P
- ;
- brk:
- warm: ld sp,stk+poff
- call poff+wrcrlf
- warm1: ld a,(poff+xz)
- out (0Ah),a
- call poff+wr$pc
- db '$'+80h
- call poff+rdbuff
- call poff+getch ;Z if eoln
- jr z,warm1
- ld de,poff+cmdtbl
- call poff+vswpc
- jr warm
- ;
- ;Error trap
- monerr: call poff+wr$pc
- db '?'+80h
- jr brk
- ;
- ;Dump [addr1[,addr2]]
- lstdmp equ $+1
- dump: ld hl,0000h
- call poff+prsadr
- dmp1: ex de,hl ;DE=start addr
- ld hl,007Fh
- ld c,l ;C=NZ flag for dump end
- add hl,de
- call poff+prsadr
- ex de,hl ;HL=start addr,DE=end addr
- dmp2: ld a,(poff+xz) ;A=page
- call poff+wra8
- call poff+wr$pc
- db ':'+80h
- ld b,16
- push hl ;Stack start of row
- call poff+wrhl16 ;Dump address
- call poff+wr$spc
- dmp3: ld a,l
- and 03h
- call z,poff+wr$spc ;write space before every 4th byte
- ld a,(hl)
- call poff+wra8
- call poff+hlcpde
- jr nz,dmp4
- ld c,0 ;set C=0 to flag end of dump
- dmp4: inc hl
- djnz dmp3
- dmp5: pop hl ;HL=start of row
- call poff+wr$spc
- ld b,16
- dmp6: ld a,l
- and 07h
- call z,poff+wr$spc ;write space before every 8th byte
- ld a,(hl)
- cp 20h
- jr nc,dmp7
- ld a,'.'
- dmp7: call poff+wr$a
- inc hl
- djnz dmp6
- ld (lstdmp+poff),hl
- call poff+wrcrlf
- inc c
- dec c
- jr nz,dmp2
- ret
- ;
- ;Go [addr1[,addr2]]
- go: call poff+prsadr
- jr nc,go1
- ld (xpc+poff),hl ;Set up target PC
- ;Set up temporary breakpoint
- go1: call poff+prsadr ;Test for temporary breakpoint
- ld a,trpskp
- jr nc,go2
- ld a,(hl) ;A=byte
- ld (hl),brkval
- ld (gbkadr+poff),hl
- ld (gbkint+poff),a
- ld a,(poff+xz)
- ld (gbkpag+poff),a
- xor a ;A=0
- go2: ld (trppat+poff),a
- ;Set up breakpoints
- ld hl,nbrk+poff
- ld b,(hl) ;B=no of breakpoints
- inc hl
- inc b
- jr go4
- go3: ld a,(hl) ;Page number
- inc hl
- out (0Ah),a ;Select page
- ld e,(hl)
- inc hl
- ld d,(hl) ;DE=address
- inc hl
- ld a,(de) ;A=previous byte
- ld (hl),a ;Store byte
- inc hl
- ld a,brkval
- ld (de),a ;Set up breakpoint
- go4: djnz go3 ;Loop for next byte
- ;Set up restart bytes
- ld hl,brkadr
- ld de,poff+xrst
- ld b,3 ;For each of 3 bytes
- go5: xor a
- ld c,a ;C=A=0
- go6: out (0Ah),a
- ld a,(hl)
- ld (de),a
- inc de
- inc c
- ld a,c
- cp 3 ;Loop for each of 3 pages
- jr c,go6
- inc hl
- djnz go5
- ;
- ld hl,brkadr
- ld bc,0300h ;B=3,C=0
- go7: ld a,c
- out (0Ah),a
- ld (hl),0C3h
- inc c
- djnz go7
- ld hl,trap+poff
- ld bc,0300h ;B=3,C=0
- go8: ld a,c
- out (0Ah),a
- ld (brkadr+1),hl
- inc l
- inc c
- djnz go8
- ;Set up registers
- xz equ $+1
- go9: ld a,00h
- out (0Ah),a
- xaf equ $+1
- ld hl,0000h
- push hl
- pop af
- xbc equ $+1
- ld bc,0000h
- xde equ $+1
- ld de,0000h
- xhl equ $+1
- ld hl,0000h
- xix equ $+2
- ld ix,0000h
- xiy equ $+2
- ld iy,0000h
- xsp equ $+1
- ld sp,0100h
- xpc equ $+1
- jp 0100h
- ;
- ;Quit JMON [addr]
- quit: call poff+wr$pc
- db 1Ah+80h ;clear screen
- call poff+prsadr ;check if an address was given
- jr nc,quit1 ;skip if no address
- ld (poff+xpc),hl ;set PC if an address was given
- jr go9 ;execute program if address given
- quit1: xor a ;else go to ROM monitor
- out (0Ah),a
- in a,(0Ah) ;Switch ROM in
- jp rommon ;Jump to ROM monitor
- ;
- ;Registers [regnum1]
- reg: call poff+getch
- jp z,disp+poff ;No parameter
- call poff+toupper
- ld e,a ;E=char
- sub 'F' ;A=0,Z if flags
- jr z,regf ;special case for flags
- call poff+prsadr
- jp nc,monerr+poff ;No value error
- push hl
- ld a,e
- ld hl,poff+regtbl
- reg1: bit 7,(hl)
- jr nz,reg3
- cp (hl)
- inc hl
- ld e,(hl)
- inc hl
- ld d,(hl)
- inc hl
- jr nz,reg1
- ex de,hl
- pop de
- ld (hl),e
- inc hl
- ld (hl),d ;store new value
- ret
- ;
- ;Special cases
- reg3: pop de ;E=new value
- cp 'A'
- ld hl,poff+xaf+1
- jr z,reg4 ;Set accumulator
- cp 'Z'
- jp nz,poff+monerr ;skip if not flags
- ld hl,poff+xz ;set page
- ;
- reg4: ld (hl),e
- ret
- ;
- ;Set flags
- regf: ld c,a ;C=flag image (initially 0)
- rgf1: call poff+getch
- jr z,rgf4 ;Exit
- call poff+toupper
- ld b,80h ;B=10000000b
- ld hl,flnam+poff ;HL=>flag names
- rgf2: cp (hl)
- jr z,rgf3
- inc hl
- or a ;CY=0
- rr b
- jr nc,rgf2
- rgferr: jp monerr+poff
- rgf3: ld a,b
- or c
- ld c,a
- jr rgf1
- rgf4: ld a,c
- ld (xaf+poff),a
- ret
- ;
- ;Set page register
- pag: call poff+prsnum
- ld de,xz+poff
- ld a,(de)
- jp nc,poff+wra8
- ld a,l
- and 03h
- ld (de),a
- ret
- ;
- ;Clear breakpoint
- clrbpt: ld hl,nbrk+poff
- ld (hl),0 ;Clear all breakpoints
- ret
- ;
- ;Break [Addr1|.]
- setbpt: call poff+prsadr
- jr nc,sbp5 ;Skip to show breakpoints
- sbp1: push hl ;Stack addr
- ld a,(poff+xz)
- ld c,a ;C=page
- ld hl,nbrk+poff
- ld b,(hl) ;B=no of breakpoints
- inc hl
- inc b
- jr sbp4
- sbp2: ld a,(hl)
- inc hl
- cp c ;Same page?
- jr nz,sbp3 ;Skip if different page
- ld e,(hl)
- inc hl
- ld d,(hl)
- dec hl ;DE=old addr
- ex (sp),hl
- call poff+hlcpde
- ex (sp),hl ;Same address?
- jr z,sbp8 ;Old address, delete it
- sbp3: inc hl
- inc hl
- inc hl
- sbp4: djnz sbp2 ;Test another address
- pop de ;DE=new addr
- ;Add a new address C:DE
- ld a,(poff+nbrk)
- cp maxbrk
- jp nc,monerr+poff ;Skip if no more room
- inc a
- ld (nbrk+poff),a
- ld (hl),c ;Store page
- inc hl
- ld (hl),e
- inc hl
- ld (hl),d
- ret
- ;
- ;Show breakpoints
- sbp5: ld hl,nbrk+poff
- ld b,(hl)
- inc hl
- inc b
- jr sbp7
- sbp6: ld a,(hl)
- inc hl
- call poff+wra8
- call poff+wr$pc
- db ':'+80h
- ld e,(hl)
- inc hl
- ld d,(hl)
- inc hl
- call poff+wrde16 ;swaps DE<->HL
- ex de,hl
- inc hl
- call poff+wrcrlf
- sbp7: djnz sbp6
- ret
- ;
- ;Toggle breakpoint off
- sbp8: pop af ;Drop old addr
- dec hl
- ex de,hl ;DE=>current entry
- ld hl,4
- add hl,de ;HL=>next entry
- ld a,b
- dec a ;A=no of entries to move
- jr z,sbp9 ;Skip if none
- add a,a
- add a,a ;A=4*no of entries to move
- ld c,a
- ld b,0 ;BC=A
- ldir ;Move entries
- sbp9: ld hl,nbrk+poff
- dec (hl)
- call poff+wr$pc
- db '-'+80h
- ret
- ;
- ;Substitue [addr]
- lstsbt equ $+1
- subst: ld hl,0000h
- call poff+prsadr
- ex de,hl ;DE=start addr
- stp1: ld a,(poff+xz)
- call poff+wra8 ;Show page:addr
- call poff+wr$pc
- db ':'+80h
- call poff+wrde16 ;Swaps DE<->HL
- ex de,hl
- call poff+wr$spc
- ld a,(de)
- call poff+wra8 ;Show old value
- call poff+wr$spc
- call poff+rdbuff ;Read a line
- inc b
- djnz stp2 ;skip if not eoln
- inc de ;step address
- jr stp1
- stp2: call poff+prsnum ;Get new value
- jr nc,stp4 ;Skip if no new value
- ld a,l
- ld (de),a ;Store new value
- inc de
- jr stp2
- stp4: cp ',' ;comma introduces string
- jr nz,stp6
- stp5: call poff+getch
- jr z,stp1 ;byte values to end of line
- ld (de),a ;store byte value
- inc de
- jr stp5
- stp6: ld (lstsbt+poff),de
- cp '.'
- jr nz,stp1 ;loop for a new line
- ret
- ;
- ;Move memory addr1,addr2,addr3
- move: call poff+prsadr
- ex de,hl ;DE=start
- call c,poff+prsadr
- push hl ;(SP)=end
- call c,poff+prsadr ;HL=dest
- jp nc,monerr+poff ;Skip if bad parameters
- call poff+hlcpde ;Is dest>=start
- ld c,l
- ld b,h ;BC=dest
- pop hl ;HL=end
- jr nc,mv2 ;If dest>=start, do lddr
- ccf
- sbc hl,de ;HL=end-start
- inc hl
- mv1: ld a,(de)
- ld (bc),a
- inc de
- inc bc
- dec hl
- ld a,h
- or l
- jr nz,mv1
- ret
- mv2: push hl ;Stack end
- sbc hl,de ;HL=end
- ld e,l
- ld d,h
- add hl,bc
- ld c,l
- ld b,h ;BC=dest end
- pop hl ;HL=end
- inc de
- mv3: ld a,(hl)
- ld (bc),a
- dec hl
- dec bc
- dec de
- ld a,d
- or e
- jr nz,mv3
- ret
- ;
- ;Fill addr1,addr2[,num]
- fill: call poff+prsadr
- ex de,hl ;DE=start
- call c,poff+prsadr
- jp nc,monerr+poff ;Bad parameters
- push hl ;End
- ld l,0
- call poff+prsnum ;CY=0
- ld c,l ;C=byte fill
- pop hl ;HL=end
- sbc hl,de ;HL=end-start
- ex de,hl ;HL=start
- inc de ;DE=count
- fl1: ld (hl),c
- inc hl
- dec de
- ld a,d
- or e
- jr nz,fl1
- ret
- ;
- ;Out addr,num
- pout: call poff+prsnum
- ld c,l ;C=port
- call c,poff+prsnum
- jr nc,perr
- ld b,l ;B=val
- out (c),b
- ret
- ;
- ;Inp addr[,num]
- pinp: call poff+prsnum
- perr: jp nc,monerr+poff
- ld c,l ;C=port
- ld l,0
- call poff+prsnum
- ld b,l ;B=val
- in b,(c)
- ld a,b
- jp poff+wra8
- ;
- ;Hex math num1[,num2]
- hmath: call poff+prsadr ;get num1
- jr nc,perr ;skip if no num1
- ex de,hl
- call poff+prsadr ;get num2
- jr c,hmath1 ;skip if got num2
- sbc hl,hl ;HL=0
- ex de,hl ;HL=num1,DE=0
- hmath1: push hl
- add hl,de
- call poff+wrhl16 ;display num1+num2
- call poff+wr$pc
- db ','+80h
- pop hl
- or a
- ex de,hl
- sbc hl,de
- jp poff+wrhl16 ;display num1-num2
- ;
- ;Subroutines
- ;
- ;HL+=A
- addhla: add a,l
- ld l,a
- ret nc
- inc h
- ret
- ;
- ;Compare HL,DE (flags=HL-DE)
- hlcpde: push hl
- or a
- sbc hl,de
- pop hl
- ret
- ;
- ;Read a null terminated string into buffer
- rdbuff: ld hl,buff+poff
- ;
- ;Read a null terminated string into $HL0
- readln: ld (rptr+poff),hl ;Store current position
- ld b,0 ;Char counter
- rl1: call poff+kbdst
- jr z,rl1 ;Wait for a char
- cp 20h
- jr c,rl3 ;Skip if control code
- cp 7Fh
- jr z,rl5 ;Skip if DEL
- ;
- ;Add char to string
- ld c,a
- ld a,b
- cp buflen
- jr nc,rl4 ;Skip if no more room
- ld a,c
- ld (hl),a
- inc hl
- inc b
- ;
- ;Echo char
- rl2: call poff+wr$a
- jr rl1 ;Another char
- ;
- ;Control codes
- rl3: cp 08h
- jr z,rl5 ;Backspace
- cp 18h
- jr z,rl6 ;Cancel
- cp 03h
- jp z,brk+poff ;CTRL-C
- cp 0Ah
- jr z,rl9 ;Exit
- cp 0Dh
- jr z,rl9 ;Exit
- ;
- ;Bad key, do a beep
- rl4: ld a,7
- jr rl2
- ;
- ;Backspace/Delete
- rl5: inc b
- dec b
- jr z,rl1
- call poff+bsb
- dec hl
- dec b
- jr rl1
- ;
- ;Cancel
- rl6: inc b
- jr rl8
- rl7: call poff+bsb
- dec hl
- rl8: djnz rl7
- jr rl1
- ;
- ;Carriage return
- rl9: ld (hl),0 ;Nul at end of string
- ;
- ;Write CRLF
- wrcrlf: call poff+wr$pc
- db 13,10+80h
- call poff+kbdst
- ret z
- cp 'S'-'@'
- ret nz
- wcl1: call poff+kbdst
- jr z,wcl1
- cp 'C'-'@'
- ret nz
- jp brk+poff
- ;
- ;Backspace, space, backspace
- bsb: call poff+wr$pc
- db 8,20h,8+80h
- ret
- ;
- ;Get char into A, Z if end of line
- getch: push hl
- rptr equ $+1
- ld hl,buff+poff
- ld a,(hl)
- or a
- jr z,gchxt ;Can't read beyond end
- inc hl
- ld (rptr+poff),hl
- gchxt: pop hl
- ret
- ;
- ;Get a char, test if in punc
- gcpunc: call poff+getch
- ;
- ;Test if A in punc, Z if yes, NZ if no
- punc: or a ;End of line?
- ret z
- cp 20h ;Space
- ret z
- cp '.' ;Dot
- ret z
- cp ',' ;Comma
- ret
- ;
- ;To upper function
- toupper:cp 'a'
- ret c
- cp 'z'+1
- ret nc
- sub a,'a'-'A'
- ret
- ;
- ;Parse address into HL, destroys A,BC, preserves DE
- ;Return NC if no number
- ;Return CY and HL=number
- ;Return CY if . (dot), HL=PC
- ;Handles . (dot) modifiers
- ;.R for relative address
- ;.A for absolute address
- ;error if bad parse
- prsadr: call poff+prsnum
- ret c ;return if a number was available
- cp '.' ;is a PC spec used?
- scf
- ccf ;CY=0
- ret nz ;return if no number here
- prsad1: ld hl,(xpc+poff) ;HL=PC
- prsad2: call poff+gcpunc ;loop for a punctuation
- jr z,prsad4 ;skip if delimiter
- call poff+toupper
- cp 'A' ;absolute spec?
- jr z,prsad5
- sub 'R' ;relative spec? A=0,Z if yes
- jr nz,prsad2 ;skip if not .R
- ;
- inc hl ;HL=PC+1
- ld c,(hl)
- inc hl
- ld b,a
- bit 7,c
- jr z,prsad3
- dec b
- prsad3: add hl,bc ;HL=relative jump target
- jr prsad2
- ;
- prsad5: inc hl
- ld a,(hl)
- inc hl
- ld h,(hl)
- ld l,a ;HL=absolute jump target
- jr prsad2
- ;
- prsad4: cp '.'
- jr z,prsad1
- scf
- ret ;return CY
- ;
- ;Parse number into HL, destroys A,BC, preserves DE
- ;Return NC if no number, HL=number, error if bad parse
- prsnum: call poff+gcpunc
- ret z ;Return if NC,Z if no number
- p160: ld hl,0000h ;Init accumulator
- p161: call poff+toupper
- sub a,'0'
- jr c,p16err ;Skip if not a number
- cp 9+1
- jr c,p162
- sub a,7
- cp 9+1
- jr c,p16err
- cp 15+1
- jr nc,p16err
- p162: add hl,hl
- add hl,hl
- add hl,hl
- add hl,hl ;HL*=16
- add a,l
- ld l,a ;HL+=A
- call poff+gcpunc
- jr nz,p161
- scf ;cause CY
- ret
- p16err: jp monerr+poff
- ;
- ;Write space, then $PC
- wrsppc: call poff+wr$spc
- ;
- ;Write $PC
- wr$pc: ex (sp),hl
- wr$pc1 ld a,(hl)
- and 7Fh
- call nz,poff+wr$a
- ld a,(hl)
- inc hl
- add a,a
- jr c,wr$pc2
- jr nz,wr$pc1
- wr$pc2: ex (sp),hl
- ret
- ;
- ;Write a space
- wr$spc: call poff+wr$pc
- db ' '+80h
- ret
- ;
- ;Display register contents from table at HL
- dspr: call poff+wr$spc ;write space
- ld a,(hl)
- inc hl
- call poff+wr$a ;write register name
- call poff+wr$pc
- db '='+80h ;write = sign
- ld e,(hl)
- inc hl
- ld d,(hl) ;DE=address of register contents
- inc hl
- push hl
- ex de,hl
- ld a,(hl)
- inc hl
- ld h,(hl) ;HL=register contents
- ld l,a
- call poff+wrhl16 ;display register contents
- pop hl
- ret
- ;
- ;Write DE hex 16
- wrde16: ex de,hl
- ;
- ;Write HL hex 16
- wrhl16: ld a,h
- call poff+wra8
- ld a,l
- ;
- ;Write A hex 8
- wra8: push af
- rrca
- rrca
- rrca
- rrca
- call poff+wra4
- pop af
- ;
- ;Write A hex 4
- wra4: and 0Fh
- cp 9+1
- jr c,wa41
- add a,7
- wa41: add a,'0'
- ;
- ;Fall into wr$a
- ;
- ;Provide subroutine wr$a
- ;write char [A] on VDU preserving all registers
- ;
- *include jvdu.z80
- ;
- ;Switch PC using case toupper(A) from table at DE, default=last entry
- vswpc: call poff+toupper
- vswpc1: ex de,hl
- vswpc2: bit 7,(hl)
- jr nz,vswpc3
- cp (hl)
- inc hl
- jr z,vswpc4
- inc hl
- inc hl
- jr vswpc2
- vswpc3: inc hl
- vswpc4: ld a,(hl)
- inc hl
- ld h,(hl)
- ld l,a
- ex de,hl
- push de
- ret
- ;
- ;Provide subroutine kbdst
- ;
- ;Returns A=ASCII key,NZ else A=0,Z if no key
- ;Preserves all other registers
- *include jkbdst.z80
- ;
- ;Command table
- cmdtbl:
- db 'B'
- dw poff+setbpt
- db 'C'
- dw poff+clrbpt
- db 'D'
- dw poff+dump
- db 'F'
- dw poff+fill
- db 'G'
- dw poff+go
- db 'H'
- dw poff+hmath
- db 'I'
- dw poff+pinp
- db 'M'
- dw poff+move
- db 'O'
- dw poff+pout
- db 'Q'
- dw poff+quit
- db 'R'
- dw poff+reg
- db 'S'
- dw poff+subst
- db 'Z'
- dw poff+pag
- db 80h
- dw poff+monerr
- ;
- flnam: db 'SZ?H?PNC'
- ;
- ;Table of register names and addresses
- regtbl: db 'B'
- dw poff+xbc
- db 'D'
- dw poff+xde
- db 'H'
- dw poff+xhl
- db 'X'
- dw poff+xix
- db 'Y'
- dw poff+xiy
- db 'S'
- dw poff+xsp
- db 'P'
- dw poff+xpc
- db 80h
- ;
- nbrk: db 0 ;number of breakpoints
- ;
- ;Boot up monitor program
- boot: ld sp,stk+poff
- call poff+wr$pc
- db 1Ah,'JMON v1.00 by J.Loke 88Jan22',13,10+80h
- ld hl,warm+poff
- ld (jmon+1+poff),hl
- jp (hl)
- pattop equ $
- if $+poff >= 0000h
- dl $+poff *** Image overflow ***
- endif
- ;
- org boot
- ds 4*maxbrk ;storage for breakpoints (grows down)
- ;contents,hi addr,lo addr,page
- xrst: ds 3*3 ;storage for bytes overwritten by RST
- buff: ds buflen ;buffer for commands
- ds stklvl*2
- stk equ $
- ;
- if $+poff >= 0000h
- dl $+poff *** Page overflow ***
- endif
- ;
- end