title SOL-20 Simulator name ('INTSOL20') ; Programm simulates 8080-code within a SOL-20 environment ; ; Call it: ; INTSOL file [startadress] ; ; The default of the startaddress is 0000H ; Written by Werner Cirsovius, December 2001 entry $memry OS equ 0000h BDOS equ 0005h TPATOP equ BDOS+1 FCB equ 005ch FCB2 equ 006ch .open equ 15 .rdseq equ 20 .setdma equ 26 .drv equ 1 .nam equ 8 .ext equ 3 _EX equ 12 _CR equ 32 OSerr equ 0ffh reclng equ 128 maxcol equ 64 ; Max columns on SOL 20 maxrow equ 16 ; Max rows on SOL 20 maxvid equ maxcol*maxrow PCbeg equ 00000h ; Default start of SOL programs SOLOS equ 0c000h ; Memory top address VDMEM equ 0cc00h ; Video top address VIDTOP equ VDMEM+maxvid ; Last memory address _CST equ 2 ; BIOS console state _CIN equ 3 ; BIOS console input _COT equ 4 ; BIOS console output null equ 00h eot equ 00h bs equ 08h tab equ 09h lf equ 0ah cr equ 0dh XON equ 'Q'-'@' XOFF equ 'S'-'@' esc equ 1bh DEL equ 7fh ; ; SOLOS keyboard - special key assignments ; down equ 9ah up equ 97h left equ 81h right equ 93h clear equ 8bh home equ 8eh backs equ 5fh ; BACKSPACE NOMSB equ 01111111b MSB equ 10000000b LOMASK equ 00001111b RSTbit equ 00111000b ; RST address mask $HL$ equ 110b ; Special register (HL) ; ; #################################################### ; ; Start interpreter ; ld sp,(TPATOP) ; Load stack ld hl,(VIDBASE) ; Get start of code ld de,maxvid add hl,de ; Allow space for video memory ld (vmemry),hl ld (BASE),hl ; Init base ld de,-VIDTOP add hl,de ; Build video offset ld (VIDOFFS),hl ld a,(FCB+.drv) ; Fetch name of file cp ' ' ; Test defined jr z,MisFile ; Nope, abort ld de,FCB2+.drv ld a,(de) ; Fetch hex digit cp ' ' ; Test defined call nz,GetLoadAdr ; Convert load address call LoadFile ; Load file jp IntLoop ; Now fall into interpreter MisFile: ld de,$$NOFILE call string ; Tell no file found jp OS ; $$NOFILE: db 'Programm simulates 8080-code within a SOL-20 environment' db cr,lf,lf db 'Call it:' db cr,lf db tab,'INTSOL file [startadress]' db cr,lf,lf db 'The default of the startaddress is 0000H' db cr,lf,eot ; ; #################################################### ; ; Initializing routines ; ; Convert load address from ^DE ; GetLoadAdr: ld ix,$$ILHXD ld hl,0 ; Init result ld b,4 ; Set max LoadLoop: ld a,(de) ; Get digit ld (ix),a ; Unpack it inc ix cp ' ' ; Test done jr z,HexRdy ; Yeap inc de call HexDig ; Convert it jr c,illHex ; Invalid add hl,hl ; Old * 16 add hl,hl add hl,hl add hl,hl or l ; Insert digit ld l,a djnz LoadLoop ; Loop on HexRdy: ld (PCreg),hl ; Set start of program ex de,hl ld hl,(vmemry) ; Get start of code or a sbc hl,de ld (BASE),hl ; Set base ret illHex: ld (ix),' ' ; Fill remainder with blanks inc ix djnz illHex ld de,$$ILLHEX call string ; Tell invalid hex digit jp OS ; $$ILLHEX: db 'Invalid hex address ' $$ILHXD: db 'xxxx' db cr,lf,eot ; ; Load SOL file ; LoadFile: ld de,FCB call open ; Open file jr z,NoFile ; Cannot find file ld de,(vmemry) ; Init load address RdFile: call setdma ; Set for disk buffer ld hl,reclng add hl,de ; Build new buffer address ld de,FCB call dskred ; Read record ex de,hl jr z,RdFile ; Still more dec de ld (EndAdr),de ; Save end address ret NoFile: ex de,hl inc hl ld de,$$FN ld bc,.nam ldir ; Unpack name of file inc de ld bc,.ext ldir ; Unpack extension ld de,$$OPNERR call string ; Tell file not found jp OS ; $$OPNERR: db 'Requested file ' $$FN: db 'xxxxxxxx.xxx not found' db cr,lf,eot ; ; Open file - Z set on open error ; open: xor a ld (FCB+_EX),a ; Init extent ld (FCB+_CR),a ; Init current record push bc push de push hl ld de,FCB ld c,.open call BDOS ; Open file cp OSerr jr popreg ; ; Set disk buffer ^DE ; setdma: call memok ; Test enough memory push bc push de push hl ld c,.setdma call BDOS ; Set buffer popreg: pop hl pop de pop bc ret ; ; Read record from file - Z flag set on success ; dskred: push bc push de push hl ld de,FCB ld c,.rdseq call BDOS ; Read from file or a jr popreg ; ; Verify memory ^DE in range ; memok: ld hl,(TPATOP) dec hl or a sbc hl,de ; Test it ret nc ; Ok ld de,$$NOMEM call string ; Tell not enough memory jp OS ; $$NOMEM: db 'Not enough memory for loading file' db cr,lf,eot ; ; #################################################### ; ; Interpreter main loop ; IntLoop: ld hl,(PCreg) ; Get current PC ld (curPC),hl ; Save it xor a ld (VidAcc),a ; No video access call TestPause ; Test pause or break call LdByte ; Load opcode ld l,a ld h,0 add hl,hl ; Double for index ld de,OpcTab add hl,de ld e,(hl) ; Fetch execution address inc hl ld d,(hl) ld hl,IntLoop push hl ; Set return address push de ret ; Execute ; ; Check memory address to be upadetd in valid range ; FixADV: ld iy,MEM$W3 call FixAdr ; Update it ret ; $$POP: db 'POP from memory',eot $$PSH: db 'PUSH to memory',eot $$CALOS: db 'Unknown SOLOS-CALL or JP to',eot $$CAL: db 'CALL or JP to',eot $$ADV: db 'INC or DEC at memory',eot $$ST: db 'Store to',eot $$ACC: db 'Accessing memory',eot $$ACT: db ' ' $$ACTadr: db 'xxxx at PC ' $$PCadr: db 'xxxx' $CRLF: db cr,lf,eot ; ; Check memory address to store into in valid range ; FixBCl: ld l,c ld h,b FixST: ld iy,MEM$W2 call FixAdr ; Update it ret ; ; Make virtual address ^HL real ; ^IY points to action block ; On SOL 20 the following action takes place: ; ; 0000...BFFF: Add offset to address for memory address in interpreter ; C000...CBFF: Error if memory modification, warning if OS address unknown ; CC00...CFFF: Error on PC access, else map to internal video memory ; D000...FFFF: Error ; ; Carry set if address updated ; FixBC: ld l,c ld h,b FixAdr: ld (CkADDR),hl ; Save address to be checked ld de,SOLOS call isMemory ; Test below OS code jr c,MapMem ; Yeap, map memory ld de,VIDTOP call isMemory ; Test above valid memory jr nc,IllMem ; Invalid, abort ld de,VDMEM call isMemory ; Test video memory jr c,VidMem ; Yeap ; ; Detected memory from C000-CBFF ; ld l,(iy+2) ; Fetch execution address ld h,(iy+3) jp (hl) ; Go ; ; Jump thru ^IY ; and ; Detected memory from CC00-CFFF ; VidMem: jpIY01: ld l,(iy+0) ; Fetch execution address ld h,(iy+1) jp (hl) ; Go ; ; Detected memory from 0000...BFFF ; MapMem: ld de,(BASE) ; Get base address add hl,de ; Make SOL PC real ret ; ; Detected memory from D000-FFFF ; IllMem: ld de,$$OUTMEM call string ; Tell invalid memory address jp OS ; $$OUTMEM: db 'Accessing memory out of SOL 20 range 0xD000' db cr,lf,eot ; ; Test HL below DE ; isMemory: or a sbc hl,de add hl,de ret ; ; Memory execution blocks ; ; First address points to action in memory C000-CBFF - SOLOS ; Second address points to action in memory CC00-CFFF - VIDEO MEMORY ; MEM$R1: dw ErrPOP,ErrPOP MEM$R2: dw WarnMem,mapVID MEM$W1: dw ErrPSH,ErrPSH MEM$W2: dw ErrWr,mapVID MEM$W3: dw IncWr,mapVID MEM$JC: dw MapOS,ErrJmp ; ; Give warning message followed by address and PC ; WarnMem: ld de,$$ACC TellAccess: call string ; Tell action ld hl,(CkADDR) ; Get address to be checked ld ix,$$ACTadr call hex16 ; Convert address ld hl,(curPC) ; Get current PC ld ix,$$PCadr call hex16 ; Convert to hex ld de,$$ACT call string ; Tell it ret ; ; Error routines ; ErrPOP: ld de,$$POP jr InvAdr ErrPSH: ld de,$$PSH jr InvAdr ErrJmp: ld de,$$CAL jr InvAdr IncWr: ld de,$$ADV jr InvAdr ErrWr: ld de,$$ST InvAdr: call TellAccess jp OS ; ; Find SOLOS address and execute it ; If not found, abort ; MapOS: ld ix,OSTAB ; Init SOLOS table ld hl,(CkADDR) ; Get address searched for ld b,OSTABl / 2 ; Set length ld de,0 ; Clear index FndOS: ld a,l cp (ix+0) ; Compare jr nz,nxtOS ld a,h cp (ix+1) jr nz,nxtOS ld hl,opcc9 push hl ; Set RET for return ld iy,OSexe add iy,de ; Position in table jp jpIY01 ; Jump thru (IY+0,1) nxtOS: inc ix ; Adjust pointer inc ix inc de ; Adjust index inc de djnz FndOS ld de,$$CALOS jr InvAdr ; Give warning ; ; Table of SOLOS v1.3 supported routines ; OSTAB: dw 0c001h ; Exit OS dw 0c004h ; Return to system entry point dw 0c019h ; SOUT: Put character to standard port dw 0c01ch ; AOUT: Put character to user port dw 0c01fh ; SINP: Get character from standard port dw 0c022h ; SINP: Get character from user port dw 0c054h ; Output character dw 0c098h ; Output character dw 0c0cbh ; Move cursor down one line dw 0c0e5h ; Home cursor dw 0c0f4h ; Clear to end of line dw 0c104h ; Move cursor up one line dw 0c11ch ; Get current screen address OSTABl equ $-OSTAB ; OSexe: dw init ; Exit OS dw retrn ; Return to system entry point dw sout ; SOUT: Put character to standard port dw aout ; AOUT: Put character to user port dw sinp ; SINP: Get character from standard port dw ainp ; AINP: Get character from user port dw VDMot ; Output character dw ochar ; Output character dw pdown ; Move cursor down one line dw phome ; Home cursor dw cline ; Clear to end of line dw pup ; Move cursor up one line dw vdadd ; Get current screen address ; ; %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% ; ; SOLOS interface ; ; System restart entry point ; init: ld de,$$EXOS call string ; Tell exit jp OS ; And exit ; $$EXOS: db '%% Restarting SOLOS - end of program' db cr,lf,eot ; ; Return to system entry point ; retrn: ld de,$$SYSENT call string ; Tell exit jp OS ; And do it ; $$SYSENT: db '%% Return to SOLOS system entry point - enter CP/M' db cr,lf,eot ; ; ---------------------------------- ; --- Get character into to ACCU --- ; ---------------------------------- ; sinp: ainp: call CST ; Get state or a ret z ; No character detected call CIN ; Get it ret ; ; ---------------------------------------- ; --- Put character in reg B to screen --- ; ---------------------------------------- ; sout: aout: ld a,l ; Copy here for sets VDMot: push hl ; Save most registers push de push bc ; ; Test if esc sequence has been started ; ld a,(escfl) ; Get escape flag or a jr nz,escs ; If non-zero go process the rest chpck: ld a,b ; Save in B...strip parity before screen! and NOMSB ; Clr parity to locate in tbl ld b,a ; Keep it w/out parity in B, too jr z,gobk ; Do a quick exit if a null ld hl,tbl ; Point to special sharacter table call tsrch ; Go process goback: call vdadd ; Get screen address ld a,(hl) ; Get present cursor character or MSB ld (hl),a ; Cursor is back on gobk: pop bc pop de ; Restore registers pop hl ret ; Exit from output routine ; ; This routine searches through a single character ; table for a match to the character in "B". If found ; a dispatch is made to the address following the matched ; character. If not found the character is displayed on ; the monitor. ; next: inc hl inc hl tsrch: ld a,(hl) ; Get chr from table or a jr z,char ; Zero is the last cp b ; Test the chr inc hl ; Point forward jr nz,next push hl ; Found one...save address call crem ; Remove cursor ex (sp),hl ; Get dispatch address to HL ld a,(hl) ; Lo addr inc hl ld h,(hl) ; Hi addr ld l,a ; HL now complete ; Here to go off to HL ex (sp),hl ; Xchg HL w/HL on stack ld a,l ; Also copy here for sets ret ; And go off to the rtn ; ; Put character to screen ; char: ld a,b ; Get character cp DEL ; IS it a DEL? ret z ; Go back if so ; ; Actually put char to screen now ; ochar: call vdadd ; Get screen address ld (hl),b ; Put chr on screen ld a,(nchar) ; Get character position cp maxcol-1 ; End of line? jr c,ok ld a,(line) cp maxrow-1 ; End of screen? jr nz,ok ; ; End of screen...roll up one line ; scroll: xor a ld (nchar),a ; Back to first char position srol: ld c,a call vdad ; Calculate line to be blanked xor a call clin1 ; Clear it ld a,(bot) inc a and maxrow-1 jp eras3 ; ; Increment line counter if necessary ; ok: ld a,(nchar) ; Get chr position inc a and maxcol-1 ; Mod 64 and wrap ld (nchar),a ret nz ; Didn't hit end of line, ok pdown: ; Cursor down one line here ld a,(line) ; Get the line count inc a cursc: and maxrow-1 cur: ld (line),a ; Store the new ret ; ; Process escape sequence ; escs: call crem ; Remove cursor call escsp ; Process the next part of sequence jp goback ; escsp: ld a,(escfl) ; Get escape flag cp -1 ; Test flag jr z,second ; ; Process third chr of esc sequence ; ld hl,escfl ld (hl),0 ; No more parts to the sequence cp 2 jr c,setx ; Set X if is one jr z,sety ; Set Y if is two cp 9 jr c,ochar ; Put it on the screen ret nz ; ; Tab absolute to value in reg B ; setx: ld a,b ; Get character jr pcur ; ; Set cursor to line "B" ; sety: ld a,b jr cursc ; ; Process second chr of esc sequence ; second: ld a,b ; Get which one cp 3 jr z,curet ; Return cursor parameters cp 4 jr nz,aret2 ; ; ESC <4> return absolute screen address ; aret: ld b,h ld c,l ; Present screen address to bc for return aret1: pop hl ; Return address pop de ; Old B push bc push hl xor a aret2: ld (escfl),a ret ; ; Return present screen parameters in "BC" ; curet: ld hl,nchar ld b,(hl) ; Character position inc hl ld c,(hl) ; Line position jr aret1 ; ; Routine to remove cursor ; crem: call vdadd ; Get current screen address ld a,(hl) and NOMSB ; Strip off the cursor ld (hl),a ret ; ; Routine to backspace ; pback: call pleft call vdadd ; Get screen address ld (hl),' ' ; Put a blank there ret ; ; Routine to process a carriage return ; pcr: call cline ; Erase any chars to the right of the cursor jr pcur ; And store the new value ; ; Routine to process a linefeed ; plf: ld a,(line) ; Get line count inc a and maxrow-1 ; See if it wrapped around jr nz,cur ; No--no need to scroll jp srol ; Yes--then scroll ; ; Set escape process flag ; pesc: ld a,-1 ld (escfl),a ; Set flag ret ; ; Erase screen ; perse: ld hl,VDMEM ; Point to screen ld (hl),MSB+' ' ; This is the cursor inc hl ; Bump 1st eras1: ; Loops here to erase screen ld (hl),' ' ; Blank it out inc hl ; Next ld a,h ; See if end of screen yet cp HIGH VIDTOP jr c,eras1 ; No--keep blanking scf ; Carry will say complete erase phome: ld a,0 ; Reset cursor--carry=erase, else home ld (line),a ; Zero line ld (nchar),a ; Left side of screen ret nc ; If no carry, we are done with home eras3: ld (bot),a ; Beginning of text offset ret ; ; Routine to move the cursor up one line ; pup: ld a,(line) ; Get line count dec a jp cursc ; Merge to handle cursor ; ; Move cursor left one position ; pleft: ld a,(nchar) dec a pcur: ; Cursor on same line and maxcol-1 ; Let cursor wrap ld (nchar),a ; Updated cursor ret ; ; Cursor right one position ; prit: ld a,(nchar) inc a jr pcur ; ; Clear to end of line ; cline: call vdadd ; Get current screen address ld a,(nchar) ; Current cursor position clin1: cp maxcol ; No more than 63 ret nc ; All done ld (hl),' ' ; All spaced out inc hl inc a jr clin1 ; Loop to end of line ; ; Routine to calculate screen address ; ; Entry at: Returns: ; ; VDADD Current screen address ; VDAD2 Address of current line, char "C" ; VDAD Line "A", character position 'C' ; vdadd: ld a,(nchar) ; Get character position ld c,a ; 'C' keeps it vdad2: ld a,(line) ; Line position vdad: ld l,a ; Into 'L' ld a,(bot) ; Get text offset add a,l ; Add it to the line position rrca ; Times two rrca ; Mades four ld l,a ; L has it and 00000011b ; Mod three for later add a,VDMEM shr 8 ; Low screen offset ld h,a ; Now H is done ld a,l ; Twist L's arm and 11000000b add a,c ld l,a ret ; H & L are now perverted ; ; Display driver command table ; ; This table defines the characters for special ; processing. If the character is not in the table it ; goes to the screen. ; tbl: db clear-MSB ; Clear screen dw perse db up-MSB ; Up cursor dw pup db down-MSB ; Down cursor dw pdown db left-MSB ; Left cursor dw pleft db right-MSB ; Right cursor dw prit db home-MSB ; Home cursor dw phome db cr ; Carriage return dw pcr db lf ; Line feed dw plf db backs ; Backspace dw pback db esc ; Escape key dw pesc db null ; End of table ; ; \ nchar: ; | ds 1 ; | Current character position line: ; | ds 1 ; | Current line position ; | ; / bot: ds 1 ; Beginning of text displacement escfl: db 0 ; Escape flag control byte ; ; %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% ; ; Calculate video memory address ; mapVID: ld hl,(CkADDR) ; Get address call getxy ; Get coordinates ld de,(VIDOFFS) ; Get offset add hl,de ; Map it ret ; ; Get coordinates x, y from video address ; ; Screen width is 64, so X/64 -> 4*X/256 ; getxy: ld a,1 ld (VidAcc),a ; Indicate video access ld ix,$$VIDadr call hex16 ; Convert address push hl add hl,hl ; *2 add hl,hl ; *4 ld a,h ; /256 and maxrow-1 ; Mask it ld (line),a ; For row pop hl push hl ld a,l and maxcol-1 ; Modulo ld (nchar),a ; For column pop hl ld a,(ScrDump) or a ; Test screen dump enabled ret z ; Nope ; ld de,$$WRVID ld a,(line) call decstrg ; Tell video access and row ld de,$$VIDROW ld a,(nchar) call decstrg ; Tell column ld de,$$VIDcls call string ; Close line ret ; VidAcc: ds 1 ScrDump: db -1 ; ; Put character stored into video memory to screen ; Vid8: ld h,a ld a,(ScrDump) or a ; Test screen dump enabled jr z,DVid8 ; Nope ld de,$$VC08 call string ; Tell character follows ld a,h jr VidVL DVid16: ld a,l call DirVidx DVid8: ld a,h DirVidx: cp ' ' ; Test printable jr c,VidCtr ; Nope cp DEL jr nc,VidCtr call COT ; Print character ret VidCtr: ld a,'.' call COT ; Indicate control character ret ; ; Put characters stored into video memory to screen ; Vid16: ld a,(ScrDump) or a ; Test screen dump enabled jr z,DVid16 ; Nope ld de,$$VC16 call string ; Tell characters follow ld a,l call VidChar ; Put them ld a,h VidVL: call VidChar call NL ret ; ; Put character to screen ; VidChar: cp ' ' ; Test printable jr z,VidSpc ; Special blank jr nc,VidOut ; Yeap push af ld a,'^' call COT ; Indicate control character pop af add a,'@' ; Make printable VidOut: cp DEL ; Test range push af call c,COT ; Echo character if printable pop af call nc,HexChar ret VidSpc: ld de,$$SPC call string ; Special blank indicator ret ; ; Print hex character ; HexChar: ld ix,$$CHRa call hex8 ld de,$$CHR call string ; Print as hex ret ; $$VC08: db 'Character to screen : ',eot $$VC16: db 'Characters to screen : ',eot $$SPC: db '',eot $$CHR: db ' char = 0' $$CHRa: db 'xxH ',eot ; ; Print message ^DE and decimal number from value in Accu ; decstrg: push af call string ; Give message pop af ; Get back value ld b,100 cp b jr c,decxxx call div255 ; Print hundreds ld b,10 call div255 ; Print tens jr prdig decxxx: ld b,10 cp b jr c,prdig call div255 ; Print tens jr prdig ; ; Print digit if in range ; div255: ld c,0 ; Init quotient divmore: cp b ; Test still in range jr c,prdig10 ; Nope sub b ; Divide inc c ; Bump quotient jr divmore prdig10: ld b,a ld a,c prdig: add a,'0' call COT ; Print units ld a,b ret ; $$WRVID: db 'Accessing video RAM at ' $$VIDadr: db 'xxxx (row=',eot $$VIDROW: db ', column=',eot $$VIDcls: db ')',cr,lf,eot ; ; Load byte from PC ; LdByte: ld de,(PCreg) ; Get current PC ld hl,(BASE) add hl,de ; Build address inc de ld (PCreg),de ; Update PC ld a,(hl) ; Get byte ret ; ; Load word from PC ; LdWord: call LdByte ; Load lo ld c,a call LdByte ; Load hi ld b,a ret ; ; Extract bits xxbbxxxx ; Bit54: rra ; Shift into right place rra rra rra and 00000011b ; Isolate bits ret ; ; Extract bits xxbbbxxx ; Bit543: rra ; Shift into right place rra rra ; ; Extract bits xxxxxbbb ; Bit210: and 00000111b ; Isolate bits ret ; ; Calculate address of register pair ; RPadr2: ld hl,RParr2 ; AF instead of SP jr RPadrc RPadr1: ld hl,RParr1 RPadrc: add a,a call addahl ; Get index into table ld e,(hl) ; Get address inc hl ld d,(hl) push de pop ix ; Copy into index register ret ; ; Calculate address of register ; Radr: ld hl,Rarr add a,a call addahl ; Get index into table ld e,(hl) ; Get address inc hl ld d,(hl) ex de,hl ; Copy into HL register ret ; ; Add Accu to reg HL ; addahl: add a,l ; Add low ld l,a ret nc inc h ; Don't forget carry ret ; RParr1: dw RP.BC dw RP.DE dw RP.HL dw RP.SP ; RParr2: dw RP.BC dw RP.DE dw RP.HL dw RP.AF ; Rarr: dw RP.BC+1 dw RP.BC dw RP.DE+1 dw RP.DE dw RP.HL+1 dw RP.HL dw RP.SP dw RP.AF+1 ; RP.AF: dw 0 RP.BC: dw 0 RP.DE: dw 0 RP.HL: dw 0 RP.SP: dw 0 PCreg: dw PCbeg ; Relative program counter curPC: ds 2 BASE: ds 2 ; Offset to code in memory EndAdr: ds 2 ; End address of file VIDBASE equ $ $memry: ds 2 ; Start of code in memory vmemry: ds 2 ; Dtto. VIDOFFS: ds 2 ; Offset from real to virtual memory CkADDR: ds 2 ; Current address checked ; ; Generic 8080 code table ; OpcTab: dw opc00 dw opc01 dw opc02 dw opc03 dw opc04 dw opc05 dw opc06 dw opc07 dw opc08 dw opc09 dw opc0a dw opc0b dw opc0c dw opc0d dw opc0e dw opc0f ; dw opc10 dw opc11 dw opc12 dw opc13 dw opc14 dw opc15 dw opc16 dw opc17 dw opc18 dw opc19 dw opc1a dw opc1b dw opc1c dw opc1d dw opc1e dw opc1f ; dw opc20 dw opc21 dw opc22 dw opc23 dw opc24 dw opc25 dw opc26 dw opc27 dw opc28 dw opc29 dw opc2a dw opc2b dw opc2c dw opc2d dw opc2e dw opc2f ; dw opc30 dw opc31 dw opc32 dw opc33 dw opc34 dw opc35 dw opc36 dw opc37 dw opc38 dw opc39 dw opc3a dw opc3b dw opc3c dw opc3d dw opc3e dw opc3f ; dw opc40 dw opc41 dw opc42 dw opc43 dw opc44 dw opc45 dw opc46 dw opc47 dw opc48 dw opc49 dw opc4a dw opc4b dw opc4c dw opc4d dw opc4e dw opc4f ; dw opc50 dw opc51 dw opc52 dw opc53 dw opc54 dw opc55 dw opc56 dw opc57 dw opc58 dw opc59 dw opc5a dw opc5b dw opc5c dw opc5d dw opc5e dw opc5f ; dw opc60 dw opc61 dw opc62 dw opc63 dw opc64 dw opc65 dw opc66 dw opc67 dw opc68 dw opc69 dw opc6a dw opc6b dw opc6c dw opc6d dw opc6e dw opc6f ; dw opc70 dw opc71 dw opc72 dw opc73 dw opc74 dw opc75 dw opc76 dw opc77 dw opc78 dw opc79 dw opc7a dw opc7b dw opc7c dw opc7d dw opc7e dw opc7f ; dw opc80 dw opc81 dw opc82 dw opc83 dw opc84 dw opc85 dw opc86 dw opc87 dw opc88 dw opc89 dw opc8a dw opc8b dw opc8c dw opc8d dw opc8e dw opc8f ; dw opc90 dw opc91 dw opc92 dw opc93 dw opc94 dw opc95 dw opc96 dw opc97 dw opc98 dw opc99 dw opc9a dw opc9b dw opc9c dw opc9d dw opc9e dw opc9f ; dw opca0 dw opca1 dw opca2 dw opca3 dw opca4 dw opca5 dw opca6 dw opca7 dw opca8 dw opca9 dw opcaa dw opcab dw opcac dw opcad dw opcae dw opcaf ; dw opcb0 dw opcb1 dw opcb2 dw opcb3 dw opcb4 dw opcb5 dw opcb6 dw opcb7 dw opcb8 dw opcb9 dw opcba dw opcbb dw opcbc dw opcbd dw opcbe dw opcbf ; dw opcc0 dw opcc1 dw opcc2 dw opcc3 dw opcc4 dw opcc5 dw opcc6 dw opcc7 dw opcc8 dw opcc9 dw opcca dw opccb dw opccc dw opccd dw opcce dw opccf ; dw opcd0 dw opcd1 dw opcd2 dw opcd3 dw opcd4 dw opcd5 dw opcd6 dw opcd7 dw opcd8 dw opcd9 dw opcda dw opcdb dw opcdc dw opcdd dw opcde dw opcdf ; dw opce0 dw opce1 dw opce2 dw opce3 dw opce4 dw opce5 dw opce6 dw opce7 dw opce8 dw opce9 dw opcea dw opceb dw opcec dw opced dw opcee dw opcef ; dw opcf0 dw opcf1 dw opcf2 dw opcf3 dw opcf4 dw opcf5 dw opcf6 dw opcf7 dw opcf8 dw opcf9 dw opcfa dw opcfb dw opcfc dw opcfd dw opcfe dw opcff ; ; 0x00 - NOP ; opc00: ret ; Do nothing ; ; 0x01, 0x11, 0x21, 0x31 - LD rp,nn ; opc01: opc11: opc21: opc31: call Bit54 ; Get reg pair index call RPadr1 ; Get address of rp call LdWord ; Load operand ld (ix+0),c ; Save it ld (ix+1),b ret ; ; 0x02, 0x12 - LD (rp),A ; opc02: opc12: call Bit54 ; Get reg pair index call RPadr1 ; Get address of rp ld l,(ix+0) ; Get content ld h,(ix+1) call FixST ; Make address real ld a,(RP.AF+1) ; Fetch accu ld (hl),a ; Store byte call Vid8 ; Put to screen if requested ret ; ; 0x03, 0x13, 0x23, 0x33 - INC rp ; opc03: opc13: opc23: opc33: ld de,+1 ; Set increment jr opcxb ; ; 0x0B, 0x1B, 0x2B, 0x3B - DEC rp ; opc0b: opc1b: opc2b: opc3b: ld de,-1 ; Set decrement opcxb: push de call Bit54 ; Get reg pair index call RPadr1 ; Get address of rp ld l,(ix+0) ; Get content ld h,(ix+1) pop de add hl,de ; Bump it ld (ix+0),l ; Bring it back ld (ix+1),h ret ; ; 0x04, 0x0C, 0x14, 0x1C, 0x24, 0x2C, 0x3C - INC r ; opc04: opc0c: opc14: opc1c: opc24: opc2c: opc3c: call Bit543 ; Get reg index call Radr ; Get address of r jr opcx4 ; Increment it ; ; 0x34 - INC (HL) ; opc34: ld hl,Vid8 push hl ; Redirect return ld hl,(RP.HL) ; Get ^HL call FixADV ; Make address real opcx4: inc (hl) ; Increment it opcx45: push af ; Save flags pop bc ; Get them back ld a,c ; Get F ld (RP.AF),a ; Save it ld a,(hl) ret ; ; 0x05, 0x0D, 0x15, 0x1D, 0x25, 0x2D, 0x3D - DEC r ; opc05: opc0d: opc15: opc1d: opc25: opc2d: opc3d: call Bit543 ; Get reg index call Radr ; Get address of r jr opcx5 ; Decrement it ; ; 0x35 - DEC (HL) ; opc35: ld hl,Vid8 push hl ; Redirect return ld hl,(RP.HL) ; Get ^HL call FixADV ; Make address real opcx5: dec (hl) ; Decrement it jr opcx45 ; Save result ; ; 0x06, 0x0E, 0x16, 0x1E, 0x26, 0x2E, 0x3E - LD r,n ; opc06: opc0e: opc16: opc1e: opc26: opc2e: opc3e: call Bit543 ; Get reg index call Radr ; Get address of r jr opcx6 ; Store it ; ; 0x36 - LD (HL),n ; opc36: ld hl,Vid8 push hl ; Redirect return ld hl,(RP.HL) ; Get ^HL call FixST ; Make address real opcx6: push hl call LdByte ; Load byte pop hl ld (hl),a ; Save it ret ; ; 0x07 - RLCA ; opc07: ld hl,(RP.AF) ; Get AF push hl pop af ; Get into real accu rlca opcx7f: push af pop hl ld (RP.AF),hl ; Save result ret ; ; 0x17 - RLA ; opc17: ld hl,(RP.AF) ; Get AF push hl pop af ; Get into real accu rla jr opcx7f ; ; 0x27 - DAA ; opc27: ld hl,(RP.AF) ; Get AF push hl pop af ; Get into real accu daa jr opcx7f ; ; 0x37 - SCF ; opc37: ld hl,(RP.AF) ; Get AF push hl pop af ; Get into real accu scf jr opcx7f ; ; 0x0F - RRCA ; opc0f: ld hl,(RP.AF) ; Get AF push hl pop af ; Get into real accu rrca jr opcx7f ; ; 0x1F - RRA ; opc1f: ld hl,(RP.AF) ; Get AF push hl pop af ; Get into real accu rra jr opcx7f ; ; 0x2F - CPL ; opc2f: ld hl,(RP.AF) ; Get AF push hl pop af ; Get into real accu cpl jr opcx7f ; ; 0x3F - CCF ; opc3f: ld hl,(RP.AF) ; Get AF push hl pop af ; Get into real accu ccf jr opcx7f ; ; 0x09, 0x19, 0x29, 0x39 - ADD HL,rp ; opc09: opc19: opc29: opc39: call Bit54 ; Get reg pair index call RPadr1 ; Get address of rp ld e,(ix+0) ; Get register value ld d,(ix+1) ld hl,(RP.HL) ; Get register HL add hl,de ; Add regs push af ld (RP.HL),hl ; Save result pop bc ; Get back F ld a,c ld (RP.AF),a ; Save F ret ; ; 0x0A, 0x1A - LD A,(rp) ; opc0a: opc1a: call Bit54 ; Get reg pair index call RPadr1 ; Get address of rp ld l,(ix+0) ; Get content ld h,(ix+1) ld iy,MEM$R2 call FixAdr ; Make address real ld a,(hl) ; Fetch byte ld (RP.AF+1),a ; Store accu ret ; ; 0x22 - LD (nn),HL ; opc22: call LdWord ; Load operand call FixBCl ; Verify correct address push hl pop ix ld hl,(RP.HL) ; Get register HL ld (ix+0),l ; Store HL ld (ix+1),h call Vid16 ; Put to screen if requested ret ; ; 0x2A - LD HL,(nn) ; opc2a: call LdWord ; Load operand ld iy,MEM$R2 call FixBC ; Verify correct address push hl pop ix ld l,(ix+0) ; Load value ld h,(ix+1) ld (RP.HL),hl ; Store into register HL ret ; ; 0x32 - LD (nn),A ; opc32: call LdWord ; Load operand call FixBCl ; Verify correct address ld a,(RP.AF+1) ; Get accu ld (hl),a ; Store it call Vid8 ; Put to screen if requested ret ; ; 0x3A - LD A,(nn) ; opc3a: call LdWord ; Load operand ld iy,MEM$R2 call FixBC ; Verify correct address ld a,(hl) ; Load byte ld (RP.AF+1),a ; Store into accu ret ; ; 0x40 - 0x7F - LD r1,r2 - except r1 | r2 = (HL) ; opc40: opc41: opc42: opc43: opc44: opc45: opc47: opc48: opc49: opc4a: opc4b: opc4c: opc4d: opc4f: opc50: opc51: opc52: opc53: opc54: opc55: opc57: opc58: opc59: opc5a: opc5b: opc5c: opc5d: opc5f: opc60: opc61: opc62: opc63: opc64: opc65: opc67: opc68: opc69: opc6a: opc6b: opc6c: opc6d: opc6f: opc78: opc79: opc7a: opc7b: opc7c: opc7d: opc7f: push af call Bit543 call Radr ; Get destination register pop af push hl call Bit210 call Radr ; Get source register ld a,(hl) pop hl ld (hl),a ; Store source ret ; ; 0x40 - 0x7F - LD r,(HL) ; opc46: opc4e: opc56: opc5e: opc66: opc6e: opc7e: call Bit543 call Radr ; Get destination register push hl ld hl,(RP.HL) ; Get register HL ld iy,MEM$R2 call FixAdr ; Verify correct address ld a,(hl) pop hl ld (hl),a ; Store (HL) ret ; ; 0x40 - 0x7F - LD (HL),r ; opc70: opc71: opc72: opc73: opc74: opc75: opc77: call Bit210 call Radr ; Get source register push hl ld hl,(RP.HL) ; Get register HL call FixST ; Verify correct address pop de ld a,(de) ; Get from source ld (hl),a ; Store into destination call Vid8 ; Put to screen if requested ret ; ; 0x76 - HALT ; opc76: ld ix,$$HADR ld de,$HALT jp pradr ; Tell halt detected and exit ; $HALT: db '%%% HALT detected at address ' $$HADR: db 'xxxx' db cr,lf,eot ; ; 0x80 - 0x87 - ADD r1,r2 - except r2 = (HL) ; opc80: opc81: opc82: opc83: opc84: opc85: opc86: opc87: ld iy,$ADD$ jr ALUdo ; ; 0x88 - 0x8F - ADC r1,r2 - except r2 = (HL) ; opc88: opc89: opc8a: opc8b: opc8c: opc8d: opc8e: opc8f: ld iy,$ADC$ jr ALUdo ; ; 0x90 - 0x97 - SUB r - except r = (HL) ; opc90: opc91: opc92: opc93: opc94: opc95: opc96: opc97: ld iy,$SUB$ jr ALUdo ; ; 0x98 - 0x9F - SBC r1,r2 - except r2 = (HL) ; opc98: opc99: opc9a: opc9b: opc9c: opc9d: opc9e: opc9f: ld iy,$SBC$ jr ALUdo ; ; 0xA0 - 0xA7 - AND r - except r = (HL) ; opca0: opca1: opca2: opca3: opca4: opca5: opca6: opca7: ld iy,$AND$ jr ALUdo ; ; 0xA8 - 0xAF - XOR r - except r = (HL) ; opca8: opca9: opcaa: opcab: opcac: opcad: opcae: opcaf: ld iy,$XOR$ jr ALUdo ; ; 0xB0 - 0xB7 - OR r - except r = (HL) ; opcb0: opcb1: opcb2: opcb3: opcb4: opcb5: opcb6: opcb7: ld iy,$OR$ jr ALUdo ; ; 0xB8 - 0xBF - CP r - except r = (HL) ; opcb8: opcb9: opcba: opcbb: opcbc: opcbd: opcbe: opcbf: ld iy,$CP$ ALUdo: call Bit210 ; Get source bits cp $HL$ ; Test (HL) jr nz,ALUr ; Nope push iy ld hl,(RP.HL) ; Get register HL ld iy,MEM$R2 call FixAdr ; Verify correct address pop iy jr ALUex ALUr: call Radr ; Get source register ALUex: ld de,(RP.AF) ; Get current AF push de pop af call jpy ; Execute ALU routine push af ; Save result pop hl ; Get AF bits ld (RP.AF),hl ; Save result ret ; ; Simple jump to ALU routine ; jpy: jp (iy) ; ; ALU routinen: A <- A ALU ^HL ; $ADD$: add a,(hl) ret $ADC$: adc a,(hl) ret $SUB$: sub (hl) ret $SBC$: sbc a,(hl) ret $AND$: and (hl) ret $XOR$: xor (hl) ret $OR$: or (hl) ret $CP$: cp (hl) ret ; ; Test if required cc bit set ; getCC: call Bit54 ; Extract cc bits srl a ; Need only two bits ld hl,CCmask call addahl ld a,(RP.AF) ; Get F and (hl) ; Get bit state ret ; CCmask: db 01000000b ; Z db 00000001b ; C db 00000100b ; E db 10000000b ; M ; ; 0xC0, 0xD0, 0xE0, 0xF0 - RET NOT cc ; opcc0: opcd0: opce0: opcf0: call getCC ; Get cc mask ret nz ; cc set jr opcc9 ; Do RET if not set ; ; 0xC8, 0xD8, 0xE8, 0xF8 - RET cc ; opcc8: opcd8: opce8: opcf8: call getCC ; Get cc mask ret z ; cc not set ; ; 0xC9 - RET ; opcc9: ld ix,PCreg call POPrp ; Pop PC ld c,(ix+0) ; Load PC ld b,(ix+1) ld iy,MEM$JC jp FixBC ; Check address ; ; 0xC2, 0xD2, 0xE2, 0xF2 - JP NOT cc ; opcc2: opcd2: opce2: opcf2: call getCC ; Get cc mask jr z,opcc3 ; Do JP if not set skpPC: ld hl,(PCreg) ; Get current PC inc hl ; Sip address inc hl ld (PCreg),hl ; Update PC ret ; ; 0xCA, 0xDA, 0xEA, 0xFA - JP cc ; opcca: opcda: opcea: opcfa: call getCC ; Get cc mask jr z,skpPC ; cc not set ; ; 0xC3 - JP ; opcc3: call LdWord ; Load word ld iy,MEM$JC call FixBC ; Check address ld (PCreg),bc ; Set new PC ret ; ; 0xC4, 0xD4, 0xE4, 0xF4 - CALL NOT cc ; opcc4: opcd4: opce4: opcf4: call getCC ; Get cc mask jr nz,skpPC ; cc set jr opccd ; Do CALL if not set ; ; 0xCC, 0xDC, 0xEC, 0xFC - CALL cc ; opccc: opcdc: opcec: opcfc: call getCC ; Get cc mask jr z,skpPC ; cc not set ; ; 0xCD - CALL ; opccd: ld hl,(PCreg) push hl inc hl ; Skip address inc hl ld (PCreg),hl ld ix,PCreg call PSHrp ; Push PC pop hl ld (PCreg),hl ; Reset PC jr opcc3 ; Do JP ; ; 0xC1, 0xD1, 0xE1, 0xF1 - POP rp ; opcc1: opcd1: opce1: opcf1: call Bit54 ; Get register bits call RPadr2 ; Get pair to be popped POPrp: ld hl,(RP.SP) ; Get stack pointer push hl ld iy,MEM$R1 call FixAdr ; Make address real ld a,(hl) ld (ix+0),a ; Do the pop inc hl ld a,(hl) ld (ix+1),a pop hl inc hl ; Fix stack pointer inc hl ld (RP.SP),hl ; Save new one ret ; ; 0xC5, 0xD5, 0xE5, 0xF5 - PUSH rp ; opcc5: opcd5: opce5: opcf5: call Bit54 ; Get register bits call RPadr2 ; Get pair to be pushed PSHrp: ld hl,(RP.SP) ; Get stack pointer push hl ld iy,MEM$W1 call FixAdr ; Make address real dec hl ld a,(ix+1) ld (hl),a ; Do the push dec hl ld a,(ix+0) ld (hl),a pop hl dec hl ; Fix stack pointer dec hl ld (RP.SP),hl ; Save new one ret ; ; 0xC6 - ADD A,n ; opcc6: ld iy,$ADD$ jr opALU8 ; ; 0xD6 - SUB n ; opcd6: ld iy,$SUB$ jr opALU8 ; ; 0xE6 - AND n ; opce6: ld iy,$AND$ jr opALU8 ; ; 0xF6 - OR n ; opcf6: ld iy,$OR$ jr opALU8 ; ; 0xCE - ADC A,n ; opcce: ld iy,$ADC$ jr opALU8 ; ; 0xDE - SBC A,n ; opcde: ld iy,$SBC$ jr opALU8 ; ; 0xEE - XOR n ; opcee: ld iy,$XOR$ jr opALU8 ; ; 0xFE - CP n ; opcfe: ld iy,$CP$ opALU8: call LdByte ; Load immediate byte ld hl,$D8$ ld (hl),a ; Save byte jp ALUex ; Do ALU operation ; $D8$: ds 1 ; ; 0xC7, 0xD7, 0xE7, 0xF7, 0xCF, 0xDF, 0xEF, 0xFF - RST n ; opcc7: opcd7: opce7: opcf7: opccf: opcdf: opcef: opcff: and RSTbit ; Isolate address ld l,a ld h,0 push hl ld ix,PCreg call PSHrp ; Push PC pop hl ld (PCreg),hl ; Set new PC ret ; ; 0xD3 - OUT (n),A ; opcd3: ld ix,$$OUTp call MapPort ; Find port message push de ld a,(RP.AF+1) ld ix,$$OUTa call hex8 ; Convert Accu to ASCII ld de,$OUTmsg call string ; Give message pop de call string ; Tell port name ld de,$$OUTp call string ; Tell port number call Conin ; Wait for any key NL: ld de,$CRLF call string ; Close line ret ; $OUTmsg: db 'OUT ' $$OUTa: db 'xx to ',eot $$OUTp: db 'xx - press any key',eot ; ; 0xDB - IN A,(n) ; opcdb: ld ix,$$INp call MapPort ; Find port message push de ld de,$INmsg call string ; Give message pop de call string ; Tell port name ld de,$$INp call string ; Tell port number call hexin ; Get byte ld (RP.AF+1),a ; Store it ret ; $INmsg: db 'IN from ',eot $$INp: db 'xx = hex : ',eot ; ; 0xE3 - EX (SP),HL ; opce3: ld hl,(RP.SP) ; Get stack pointer ld iy,MEM$W1 call FixAdr ; Make address real ld de,(RP.HL) ; Fetch register ld a,(hl) ; Get from stack ld (RP.HL),a ; Swap ld (hl),e inc hl ld a,(hl) ld (RP.HL+1),a ld (hl),d ret ; ; 0xE9 - JP (HL) ; opce9: ld hl,(RP.HL) ; Fetch register ld (PCreg),hl ; Set new PC ld c,l ; Load PC ld b,h ld iy,MEM$JC jp FixBC ; Check address ; ; 0xED - EX DE,HL ; opceb: ld hl,(RP.HL) ; Fetch registers ld de,(RP.DE) ld (RP.HL),de ; Swap registers ld (RP.DE),hl ret ; ; 0xF3 - DI !! Ignored here ; 0xFB - EI !! Ignored here ; opcf3: opcfb: ret ; ; 0xF9 - LD SP,HL ; opcf9: ld hl,(RP.HL) ; Fetch register ld (RP.SP),hl ; Unpack it ret ; ; 0x08, 0x10, 0x18, 0x20, 0x28, 0x30 ; 0x38, 0xCB, 0xD9, 0xDD, 0xED, 0xFD - Z80 codes not supported here ; opc08: opc10: opc18: opc20: opc28: opc30: opc38: opccb: opcd9: opcdd: opced: opcfd: ld ix,$$OPC call hex8 ; Convert opcode to ASCII ld ix,$$ADR ld de,$INV pradr: ld hl,(curPC) ; Get current PC call hex16 ; Convert to hex call string jp OS ; $INV: db '%%% Invalid Z80-code ' $$OPC: db 'xx at address ' $$ADR: db 'xxxx' db cr,lf,eot ; ; ---------------------- ; &&& SYSTEM SUPPORT &&& ; ---------------------- ; ; Put character to console thru BIOS ; COT: push de ld de,3*(_COT-1) ; Load BIOS vector jr BIOSgo ; ; Get character from console thru BIOS ; CIN: push de ld de,3*(_CIN-1) ; Load BIOS vector jr BIOSgo ; ; Get keyboard state thru BIOS ; CST: push de ld de,3*(_CST-1) ; Load BIOS vector BIOSgo: push bc push hl ld c,a ; Unpack possible character ld hl,BIOSret push hl ; Set return address ld hl,(OS+1) add hl,de ; Build BIOS vector jp (hl) ; Enter routine BIOSret: pop hl pop bc pop de ret ; ; Print string ^DE on console ; string: push bc push de push hl strggo: ld a,(de) ; Get character or a ; Test end jr z,strgend ; Yeap call COT ; Print it inc de jr strggo strgend: pop hl pop de pop bc ret ; ; Get key from console ; Conin: call CST ; Get state or a jr nz,Conin ; Wait until key pressed call CIN ; Get it call upcase ; Convert to upper case Abort: cp 'C'-'@' ; Test abort ret nz ; Nope ld hl,(curPC) ; Get current PC ld ix,$$ABPC call hex16 ; Convert to hex ld de,$ABORT call string ; Tell abort jp OS ; Exit ; $ABORT: db cr,lf db '^C detected at PC = ' $$ABPC: db 'xxxx - abort' db cr,lf,eot ; ; Convert character to upper case ; upcase: cp 'a' ; Test case ret c cp 'z'+1 ret nc add a,'A'-'a' ; Convert ret ; ; Test pause requested ; TestPause: call sinp ; Get state or character from keyboard or a ret z ; No input call Abort ; Test abortion cp 'T'-'@' ; Test screen output toggle jr nz,TstXOFF ; Nope ld a,(ScrDump) cpl ; Toggle flag ld (ScrDump),a ret TstXOFF: cp XOFF ; Test pause ret nz ; Nope ld de,$$PAUSE call string ; Tell pausing WtXON: call sinp ; Get next character from keyboard or a jr z,WtXON ; No input call Abort ; Test abortion cp XON ; Test continue jr nz,WtXON ; Nope ret ; $$PAUSE: db 'Output paused - continue with XON' db cr,lf,eot ; ; Convert 16 bit hex HL to ASCII ^IX ; hex16: ld a,h call hex8 ; Convert hi ld a,l ; Then lo ; ; Convert 8 bit hex ACCU to ASCII ^IX ; hex8: push af rra ; Get upper bits rra rra rra call hex4 ; Convert to ASCII pop af hex4: and LOMASK ; Mask lower bits add a,90h ; Convert to ASCII daa adc a,40h daa ld (ix),a ; Store digit inc ix ret ; ; Input hex byte ; hexin: ld c,0 ; Clear result ld b,c ; Clear count readhex: call Conin ; Get character cp DEL ; Test delete jr z,delhex cp bs jr z,delhex cp cr ; Test new line jr z,endhex cp lf jr z,endhex ld d,a ; Save character call HexDig ; Get hex digit jr c,readhex ; Not valid ld e,a ; Save digit ld a,b cp 2 ; Test max jr z,readhex ; Ignore ld a,d call COT ; Echo character ld a,c rlca ; *16 rlca rlca rlca add a,e ; Insert digit ld c,a inc b jr readhex delhex: inc b dec b ; Test any input jr z,readhex ; Nope ld de,$$BS call string ; Delete character dec b ; Fix count jr z,hexin ; Total new ld a,c rrca ; Fix input rrca rrca rrca ld c,a jr readhex endhex: call NL ; Close line ld a,b sub 1 ; Build carry on empty input sbc a,a ld a,c ret ; $$BS: db bs,' ',bs,eot ; ; Get hex digit - C set says not a digit ; HexDig: sub '0' ; Strip off offset ret c ; Invalid cp 9+1 ; Test range ccf ret nc ; Range 0..9 sub 'A'-'0'-10 ; Fix for hex offset cp 10 ret c ; Invalid cp 15+1 ccf ret ; ; Port assignments ; serst equ 0f8h ; Serial status port sdata equ 0f9h ; Serial data stapt equ 0fah ; Status port general tappt equ 0fah ; Tape status port tdata equ 0fbh ; Tape data kdata equ 0fch ; Keyboard data pdata equ 0fdh ; Parallel data dstat equ 0feh ; VDM display parameter port sense equ 0ffh ; Sense switches ; ; Map port message ; MapPort: call LdByte ; Fetch port push af ; Save it call hex8 ; Convert port to ASCII pop af ; Get back port sub serst ; Test known one ld de,$$P_XX ret c ; Nope, return default add a,a ld hl,$$PORTS call addahl ; Point to table ld e,(hl) ; Fetch message inc hl ld d,(hl) ret ; $$PORTS: dw $$P_F8,$$P_F9,$$P_FA,$$P_FB dw $$P_FC,$$P_FD,$$P_FE,$$P_FF $$P_XX: db 'port ',eot $$P_F8: db 'serial status port ',eot $$P_F9: db 'serial data ',eot $$P_FA: db 'status port general ',eot $$P_FB: db 'tape data ',eot $$P_FC: db 'keyboard data ',eot $$P_FD: db 'parallel data ',eot $$P_FE: db 'VDM display parameter port ',eot $$P_FF: db 'sense switches ',eot end