; ******************************************************* ; FILE: DGZ80OSII.asm ; Version 2013/08/28 ; Greg Peterson ; ; The Digital Group - Z80 OS ; ; THIS IS THE OS CODE READ FROM THE AUDIO TAPE BY THE EPROM LOADER ; ; This is the original code that came with the Z-80 board. A ; subsequent version was released (around April 1977 I believe). ; That version had improved cursor control. There is a configuration ; switch below 'PATCH1' that will insert the changes for you. ; ; Translated to Zilog mnmonics ! ; ; THE ORIGINAL DG Z-80 BOARD OPERATED WITH A 2.5 MHZ CRYSTAL. ; ; Notes: ; This code assembles without error using the Zilog assembler. ; The Z80 is not one of the supported processors, so tell the ; assembler to use the Z80180 as the target processor. This is ; a great tool available for free at Zilog.com if you give them ; some contact info. This is a macro capable relocating assembler, ; far more powerful than you need for this, but the best free ; assembler I have seen bar none. ; ; I refer to DG ASCII in the code. In The Digital Group software, ; the MSB of all characters is set. It comes that way from the ; keyboard, and is presented that way to the CRT. I would have ; stripped and added bit 7 as needed so I was working with ; standard ASCII, but not DG. So if you try to cross character ; codes through an ASCII chart, remember to strip bit 7 to make ; sense of it all. ; ; There is a great deal of attention paid to character spacing ; in this code. As I remember, DG did not have a cursor on their ; monitor initially. So alter screen layouts with care. ; ; This code is fairly primitive for a monitor, let alone an OS. ; It does support both Octal and Hex bases for number display ; and entry. Dr. Robert Suding, who I believe wrote this code in ; the early to mid 1970's, liked Octal. That never really caught ; on it seems. This code can read and write cassettes, with the ; OS the default code to read and write. It can use other areas, ; but you have to alter memory values. The OS will dump memory ; to the screen, and allow the user to poke new values in. ; It will display the CPU registers, and supports a breakpoint ; capability. ; ; Labels have been extensively changed to more clearly reflect ; what is happening in the code. Labels like 'X1' might now be ; something like "BITLOOP". ; ; The code is overcommented, so disregard the obvious. ; The cryptic numbers following many labels as comments are the ; memory address in Octal and Hex of that label in the original ; code. If you look for that label, it will likely be called ; something else, but it will be at that address. ; ; When assembled, if the hex comment addresses do not match ; what the assembler churns out, you have a problem somewhere. ; Even if they do match up, problems can still lurk in the code, ; but they are far less likely. ; ; Since many DG programs made calls into the loader ROM on ; the CPU board, or into this OS, for standard subroutines, be ; very careful about moving things around or you will break ; things like the DG assembler, DG Basic, etc. ; ; ******************************************************* ; The patching instructions were: ; Replace bytes 003 346 - 004 377 ; Replace bytes 001 233 - 001 246 ; ; Move bytes from 005 225... to 005 124... ; ******************************************************* ; Configuration switches PATCH1: EQU 0FFFFH ; TRUE TO INSERT OS PATCHES ;PATCH1: EQU 0000H ; FALSE TO USE ORIGINAL CODE ; ******************************************************* ; I/O Space definitions CASPORT: EQU 01H ; R/W CASSETTE DATA ON BIT 0 TVPORT: EQU 00H ; PORT FOR VIDEO on write ; KBD data on a read ; Magic Numbers RSCONST: EQU 1FH ; READ SPEED CONSTANT, INITIAL VALUE ; AKA # of samples per serial bit cell ; USERAREA: EQU 0600H ; DEFAULT AREA FOR USER PROGRAMS ; ******************************************************* ; External References to code in the boot loader EPROM TVERASE: EQU 00E6H ; erase the crt screen TVPUTSP: EQU 00F8H ; Print one space on the CRT TVPUTCH: EQU 00FAH ; Print ASCII in A on the CRT STARTREAD: EQU 0077H ; START READ IN PROM ; ******************************************************* ; PUBLIC - Code, etc. in OS others may wish to use ; OPMONITOR: EQU 0500H ; Start the OS by jumping here ; DEFAULTUSER: EQU 0600H ; DEFAULT USER PROGRAMMING AREA ; DUEND: EQU 07FFH ; End of user programming area. ; ; I have no list of useful subroutines used by other DG ; programs. You should approach moving anything around ; with extreme caution. ORG 0100H ; THIS CODE RUNS AT 0100H SIGNATURE: DB 53H ; 123 OCTAL - THIS IS A SIGNATURE DB 53H ; And this is too ; *************************************************** ; RESTART COMMANDS ARE VECTORED HERE FROM EPROM ; Obviously, supporting code TBD RS1: JP 0000H ; RS2: JP 0000H ; RS3: JP 0000H ; RS4: JP 0000H ; RS5: JP 0000H ; RS6: JP 0000H ; RS7: JP 0000H ; ; ************************************************ ; VARIOUS CASSETTE VARIABLES STORAGE ; I CALL THIS THE TAPE CONTROL BLOCK - TCB ORG 0117H ; EPROM Loader expects this here TCB: TAPESPEED: DB 18H ; CASSETTE SPEED CONSTANT ; 18H IS 1100 BAUD AT 2.5 MHZ XTAL STARTADDR: DW 0000H ; PUT THE CODE STARTING HERE ENDADDR: ; STOP LOADING WHEN YOU GET HERE DW 0000H RESERVED: DB 00H ; Undefined, unused ; ************************************************* ; NMI VECTOR COMES THRU HERE ORG 011DH NMIVEC: JP 0000H ; NMI RESTART ; ************************************************* ; COMMAND. ; WRITE A BLOCK OF DATA TO TAPE. (The OS really). ; ; No values are passed in, default memory area is used. ; DE is used to point to data in memory to send ; HL is used as a general memory pointer ; ; WRITE2K: ; 001 040 0120H WSETUP2K: LD HL,STARTADDR ; Point to TCB LD (HL),00H ; SET START ADDR TO 0100H INC L ; LD (HL),01H ; INC L ; LD (HL),0FFH ; SET END ADDR TO 07FFH INC L ; LD (HL),07H ; LD HL,WRITEMSG ; "Writing" CALL TVPUTMSG ; 0200H WRITELEADIN: ; 001 064 0134H ; Magic #: 65H = 101 decimal = 0110 1001 Binary. ; Delay 100 ms for each count in A, so 65H is ; 10 seconds + .1 seconds, and it must be an odd ; number for bit 0 to be a 1 and cause a mark tone. ; This is a clever but problematic use of code. LD A,65H ; 10.1 SECONDS OUT (CASPORT),A ; MARK TONE LEADER CALL SECONDS ; MAKE 10 SECONDS OF MARK TONE LD DE,(STARTADDR) ; LOAD START ADDRESS WRITELOOP: ; 001 077 013FH CALL BYTEWRITE ; WRITE ONE BYTE TO TAPE ; CHECK IF DONE - 16 bit compare LD HL,(ENDADDR) ; HL <= ENDING ADDRESS INC HL ; Include last byte in the transfer INC DE ; Where we are loading += 1 XOR A ; CLEAR CARRY SBC HL,DE ; HL <= HL - DE & set flags JR NZ,WRITELOOP ; Loop IF current != end addr ; Fall thru when all bytes written ; Note: A Mark tone should be present on CASPORT ; from the 2 stop bits of the final byte of data ; when we get here. WRITELEADOUT: ; 001 114 014CH LD A,32H ; 5 SECONDS OF MARKING LEADOUT CALL SECONDS ; JP OPMONITOR ; Enter Z-80 OS ; ****************************************** ; WRITE A SINGLE BYTE AT (DE) TO TAPE. ; ; H holds the bit counter ; DE points to data in memory to send BYTEWRITE: WRITESETUP: ; 001 124 0154H LD H,09H ; 8 data bits + 1 start bit XOR A ; Cy = 0 for start bit LD A,(DE) ; A <= data to send RLA ; Start bit in CY to bit 0 WBITLP: ; 001 131 0159H ; Send bit 0 of A to the tape, other bits ; of A are ignored OUT (CASPORT),A ; Only bit 0 matters here CALL TIMEDELAY ; Time out bit cell RRA ; ROTATE A RIGHT DEC H ; Bit counter -= 1 JR NZ,WBITLP ; SEND EACH BIT LD A,01H ; Load a mark tone OUT (CASPORT),A ; SEND CALL TIMEDELAY ; 1 STOP BIT CALL TIMEDELAY ; ANOTHER STOP BIT RET ; ; ********************************************* ; THIS IS A BIT TIME DELAY ROUTINE, DESIGNED TO DELAY ; FOR 1 BIT TIME AT 1100 BAUD WITH A 2.5 MHZ Z-80 TIMEDELAY: ; 001 155 016DH PUSH AF ; Preserve context LD A,(TAPESPEED) ; LOAD TAPE SPEED CONSTANT ADD A,A ; X2 ADD A,A ; X4 LD B,A ; SPEED X 4 TO B PUSH HL ; DUMMY OP BITLP: ; 001 165 NOP ; DUMMY OP DJNZ BITLP ; POP HL ; DUMMY OP POP AF ; Restore context RET ; Exit TIMEDELAY ; ********************************** ; PRESET A TO # OF 1/10 SECONDS TO ELAPSE BEFORE RETURNING. ; A,C,D CLEARED ; ; This is used for the longer delays associated with tape ; leadin and leadout. The code is critically dependent on ; processor speed. ; ; A = # of seconds/10 to delay, passed in ; D = Loaded with # of 1/10 seconds to delay ; C = Loaded with magic # for 1/10 second delay SECONDS: ; 001 173 017BH LD D,19H ; Magic # to delay 1/10 second TENTHSLOOP: ; 001 175 LD BC,0003H ; More magic. SECLOOP: ; 001 200 0180H DJNZ SECLOOP ; 256 loops for B == 0 DEC C ; JR NZ,SECLOOP ; 256 * 3 == 768 loops DEC D ; Time out 1/10 second count JR NZ,TENTHSLOOP ; 768 * 19H == 19,200 loops DEC A ; JR NZ,SECONDS ; Time out seconds/10 RET ; Exit SECONDS ; ****************************************** ; MESSAGE TO TELL THE OPERATOR WE ARE WRITING WRITEMSG: ; 001 214 018CH DB 0FFH ; HOME ERASE DB 6CH ; SPACES DB 'W' + 80H ; DB 'r' + 80H ; DB 'i' + 80H ; DB 't' + 80H ; DB 'i' + 80H ; DB 'n' + 80H ; DB 'g' + 80H ; DB 00H ; RETURN ; ****************************************** ; Print a '?' on the monitor PUTQUES: ; 001 226 0196H LD A,'?' + 80H ; LOAD A WITH '?' JP PUTC ; ; ############################### IF PATCH1 ; IF WE ARE PATCHING THE OS HLOUT: ; 001 233 019BH CALL TVERASE ; 000 346 00E6H LD A,D ; CALL PUTC ; 000 372 00FAH CALL ASCII ; 001 242 01A2H GET & PRINT PAGE/BYTE RET ; ; ############################### ELSE ; WE ARE NOT PATCHING THE OS ; USE ORIGINAL CODE ; ****************************************** ; Return 2 hex digits in B ; This is used by ASCIIHEX (and ONLY by ASCIIHEX) ; to complete the loading of 2 hex digits. ; A very strange way to program! HEXLS: ; 001 233 019BH RLCA ; LD B,A ; B <= MS hex nibble CALL KBHEX ; A <= one KB HEX CHAR OR B ; add in LS hex nibble RET ; Exit ASCIIHEX, data in B ; ******************************************************** ; SOME VARIABLES DB 00H ; NOT USED DB 00H ; NOT USED DB 00H ; NOT USED DB 00H ; NOT USED ENDIF ; DONE PATCHING THE OS ; ############################### ; Intlvl is set to 0 by OPMONITOR & displayed by TVDUMP ; but it is not used anywhere else. INTLVL: DB 00H ; INTERRUPT LEVEL INDICATOR ; OCTAL / HEX CONSTANT - determines base of displayed #'s OHCONST: DB 00H ; 'H' + 80H if we are using HEX ; ELSE Octal. ; ************************************************ ; READ AN ASCII CHARACTER FROM THE KEYBOARD; ; KEYPRESS STROBE IS ON MSB (BIT 7): ; LOOP, READING KBD, WAITING FOR STROBE TO GO HIGH. ; SAVE KBD CHAR. ; WAIT FOR STROBE TO GO LOW. ; RETURN SAVED ASCII KBD CHAR IN A. ; Note: Strobe on bit 7 will be returned HIGH; DG ASCII ; KBGETCH: ; 001 250 01A8H IN A,(TVPORT) ; A <= KBD ASCII BIT 7,A ; JR NZ,KBGETCH ; IF STROBE ON BIT 7 HI, WAIT PUSH AF ; STROBE LOW, SAVE DATA KBLP: IN A,(TVPORT) ; BIT 7,A ; JR NZ,KBLP ; Wait for strobe to go low POP AF ; A <= Kbd data RET ; Exit KBGETCH ; ************************************************ ; CONVERT BINARY BYTE PASSED IN E TO OCTAL & PRINT ON CRT. ; E IS USED AS A DIGIT COUNTER; RETURN A CLEARED. OCTALCHAR: ; 001 267 01B7H LD A,E ; VALUE TO PRINT OR A ; CLEAR CARRY FOR ROTATES TO FOLLOW LD E,03H ; PRINT 3 OCTAL DIGITS OCTDIGLP: ; 001 273 RLA ; POSITION MS DIGIT RLA ; RLA ; ROTATE LEFT THRU CARRY PUSH AF ; SAVE VALUE NOT YET PRINTED AND A,07H ; MASK OFF DIGIT CALL TVPUTNUM ; PRINT ON CRT POP AF ; REST OF DIGITS TO PRINT DEC E ; DIGIT COUNT -= 1 JR NZ,OCTDIGLP ; NO, PRINT MORE RET ; ; ************************************ ; THIS IS THE STACK AREA USERSTACK: ; 001 311 01C9H DS 55 ; USER STACK TOS: ; 001 377 TOP OF STACK ; ********************************************** ; PRINT A DG ASCII MESSAGE, POINTED TO BY HL, ON ; THE CRT UP TO A TERMINATING NULL WITH EMBEDDED ; SPACES. ; ; THE MESSAGE HAS THE FOLLOWING FORMAT: ; ; 0FFH ERASES THE SCREEN & HOMES THE CURSOR. ; 00H (NULL) ENDS THE MESSAGE ; AN ASCII CHARACTER TO PRINT HAS BIT 7 SET. ; ANY OTHER VALUE (01H TO 0EFH) IS A SPACE COUNT, ; AND THAT NUMBER OF SPACES ARE PRINTED. ; ; A, B, C, E, H & L ALL TRASHED. ; TVEDITOR: ; 002 000 0200H TVPUTMSG: TVMSGLOOP: LD A,(HL) ; FETCH MESSAGE CHAR ERASECHECK: ; 002 001 0201H CP 0FFH ; HOME ERASE ? JR NZ,ASCIICHECK ; NO CALL TVERASE ; YES, ERASESCREEN JR NXTMSGCH ; NEXT MESSAGE CHARACTER ASCIICHECK: ; 002 012 020AH BIT 7,A ; BIT 7 SET ? JR Z,ENDCHECK ; NO CALL TVPUTCH ; PRINT ASCII in A JR NXTMSGCH ; NEXT CHAR ENDCHECK: ; 002 023 0213H ; CP 00H ; A 00H ? RET Z ; YES, MESSAGE DONE, EXIT EDITOR SPACELOOP: ; 002 026 0216H PUSH AF ; NO, IT IS A SPACE COUNT CALL TVPUTSP ; PRINT A SPACE POP AF ; DEC A ; SPACE COUNT -= 1 JR NZ,SPACELOOP ; NXTMSGCH: ; INC HL ; Message pointer += 1 JR TVPUTMSG ; & loop ; ***************************************** ; PRINT BINARY PASSED IN E AS 2 HEX DIGITS ; ON THE MONITOR. TVPUTHEX: ; 002 041 0221H CALL TVPUTSP ; Space over LD A,E ; MS nibble RRCA ; MOVE DOWN TO LS RRCA ; RRCA ; RRCA ; CALL HEXOUT ; PRINT MS LD A,E ; Get LS nibble CALL HEXOUT ; PRINT LS RET ; ; ************************************* ; PRINT LS NIBBLE OF A AS 1 HEX CHARACTER ; Note: Different print routines for numbers & ASCII HEXOUT: ; 002 061 0231H AND A,0FH ; MASK OFF LS NIBBLE CP 10 ; A <= 10 Decimal ? JR C,TVPUTNUM ; YES, print number ; ELSE # in range A .. F, fall thru SUB 09H ; Convert A .. F OR 0C0H ; Make DG ASCII CALL TVPUTCH ; PRINT ASCII in A RET ; ; ******************************** ; Print binary number (0 .. 9) in A as ASCII TVPUTNUM: ; 002 077 023FH OR A,'0' + 80H ; Convert number to ASCII CALL TVPUTCH ; PRINT ASCII in A RET ; Exit HEXOUT ; ******************************** ; PRINT BINARY BYTE AT (HL) AS OCTAL OR HEX ; ; HL = address of byte ; E = Byte to print as Octal or Hex OHPRINTMEM: ; 002 105 0245H LD E,(HL) ; FETCH CHARACTER AT (HL) ; Fall thru to print it ; ******************************** ; Print byte in E as OCTAL or HEX OHPUTCH: LD A,(OHCONST) ; 002 106 0246H CP 'H' + 80H ; A == "H" for HEX ? JP Z,TVPUTHEX ; ITS HEX, Branch ; Anything else is OCTAL ; Fall thru JP OCTALCHAR ; ELSE DEFAULT TO OCTAL ; ********************************* ; TITLEREGSMSG: ; 002 121 0251H DB 0FFH ; HOME ERASE DB 08H ; SPACES DB 'T' + 80H ; 'TV STORAGE DUMP' ; DB 'V' + 80H ; DB ' ' + 80H ; DB 'S' + 80H ; DB 'T' + 80H ; DB 'O' + 80H ; DB 'R' + 80H ; DB 'A' + 80H ; DB 'G' + 80H ; DB 'E' + 80H ; DB ' ' + 80H ; DB 'D' + 80H ; DB 'U' + 80H ; DB 'M' + 80H ; DB 'P' + 80H ; DB 09H ; SPACES DB 'R' + 80H ; 'Registers:' DB 'e' + 80H ; DB 'g' + 80H ; DB 'i' + 80H ; DB 's' + 80H ; DB 't' + 80H ; DB 'e' + 80H ; DB 'r' + 80H ; DB 's' + 80H ; DB ':' + 80H ; DB 19H ; SPACES DB 'A' + 80H ; DB 03H ; DB 'B' + 80H ; DB 03H ; DB 'C' + 80H ; DB 03H ; DB 'D' + 80H ; DB 03H ; DB 'E' + 80H ; DB 03H ; DB 'H' + 80H ; DB 03H ; DB 'L' + 80H ; DB 06H ; SPACES DB 00H ; RETURN ; ******************************** ; ALTREGSMSG: ; 002 175 027DH DB 06H ; SPACES DB 'A' + 80H ; DB 0A7H ; "'" + 80H DB 02H ; SPACES DB 'B' + 80H ; DB 0A7H ; "'" + 80H DB 02H ; SPACES DB 'C' + 80H ; DB 0A7H ; "'" + 80H DB 02H ; SPACES DB 'D' + 80H ; DB 0A7H ; "'" + 80H DB 02H ; SPACES DB 'E' + 80H DB 0A7H ; "'" + 80H DB 02H ; SPACES DB 'H' + 80H DB 0A7H ; "'" + 80H db 02H ; SPACES DB 'L' + 80H ; DB 0A7H ; "'" DB 05H ; SPACES DB 00H ; RETURN ; ******************************** ; FLAGSMSG: ; 002 224 0294H DB 23H ; SPACES DB 'F' + 80H ; 'FLAGS:' DB 'l' + 80H ; DB 'a' + 80H ; DB 'g' + 80H ; DB 's' + 80H ; DB ':' + 80H ; DB 1CH ; SPACES DB 'S' + 80H ;'S Z H P N C' DB ' ' + 80H ; DB 'Z' + 80H ; DB ' ' + 80H ; DB 'H' + 80H ; DB ' ' + 80H ; DB 'P' + 80H ; DB ' ' + 80H ; DB 'N' + 80H ; DB ' ' + 80H ; DB 'C' + 80H ; DB 04H ; SPACES DB 'S' + 80H ; 'S'Z'H'P'N'C' DB 0A7H ; "'" + 80H DB 'Z' + 80H ; DB 0A7H ; "'" + 80H DB 'H' + 80H ; DB 0A7H ; "'" + 80H DB 'P' + 80H ; DB 0A7H ; "'" + 80H DB 'N' + 80H ; DB 0A7H ; "'" + 80H DB 'C' + 80H ; DB 0A7H ; "'" + 80H DB 05H ; SPACES DB 00H ; RETURN ; ******************************** ; DS 05H ; ; ******************************** ; INDEXMSG: ; 002 273 02BBH ; DB 20H ; SPACES DB 'X' + 80H ; 'X Index' DB ' ' + 80H ; DB 'I' + 80H ; DB 'n' + 80H ; DB 'd' + 80H ; DB 'e' + 80H ; DB 'x' + 80H ; DB 02H ; SPACES DB 'Y' + 80H ; 'Y Index' DB ' ' + 80H ; DB 'I' + 80H ; DB 'n' + 80H ; DB 'd' + 80H ; DB 'e' + 80H ; DB 'x' + 80H ; DB 03H ; SPACES DB 'I' + 80H ; 'I Reg' DB ' ' + 80H ; DB 'R' + 80H ; DB 'e' + 80H ; DB 'g' + 80H ; DB 03H ; SPACES DB 'R' + 80H ; 'R Reg' DB ' ' + 80H ; DB 'R' + 80H ; DB 'e' + 80H ; DB 'g' + 80H ; DB 01H ; SPACES DB 00H ; return ; ******************************** ; STACKMSG: ; 002 331 02D9H DB 021H ; Spaces DB 'S' + 80H ; 'Stack' DB 't' + 80H ; DB 'a' + 80H ; DB 'c' + 80H ; DB 'k' + 80H ; DB 04H ; SPACES DB 'R' + 80H ; 'Return?' DB 'e' + 80H ; DB 't' + 80H ; DB 'u' + 80H ; DB 'r' + 80H ; DB 'n' + 80H ; DB '?' + 80H ; DB 04H ; SPACES DB 'I' + 80H ; 'Interrupt ' DB 'n' + 80H ; DB 't' + 80H ; DB 'e' + 80H ; DB 'r' + 80H ; DB 'r' + 80H ; DB 'u' + 80H ; DB 'p' + 80H ; DB 't' + 80H ; DB ' ' + 80H ; DB 00H ; RETURN ; ******************************** ; PAGEMSG: ; 002 363 02F3H DB 0FFH ; Home erase DB 'E' + 80H ; 'Enter Page ' DB 'n' + 80H ; DB 't' + 80H ; DB 'e' + 80H ; DB 'r' + 80H ; DB ' ' + 80H ; DB 'P' + 80H ; DB 'a' + 80H ; DB 'g' + 80H ; DB 'e' + 80H ; DB ' ' + 80H ; DB 00H ; SPACES ; ****************************************** ; COMMAND. ; Dump memory to the video screen in Octal or Hex. ; ; Operator inputs: ; Space = display next memory page ; P = goto KBD Programming to alter memory ; Snn where nn = hex or octal #: Set memory page to dump ; R = Return to Op monitor (command input loop) TVDUMP: ; 003 000 0300H PUSH AF ; PUT PRIMARY REGS ON STACK PUSH BC ; PUSH DE ; PUSH HL ; EX AF, AF' ; SWAP IN ALTERNATE REGS EXX ; PUSH AF ; PUT ALTERNATES ON STACK PUSH BC ; PUSH DE ; PUSH HL ; EX AF, AF' ; RESTORE PRIMARY REGS EXX ; PUSH IX ; PUT INDEX REGS ON STACK PUSH IY ; LD A,I ; PUT INTERRUPT VECTOR LD B,A ; LD A,R ; AND REFRESH REGISTER LD C,A ; PUSH BC ; ON THE STACK LD HL,0000H ; CLEAR HL ADD HL,SP ; COPY SP TO HL LD B,18H ; 24D items we pushed on stack TVADDLP1: ; 003 035 031DH INC HL ; HL <= HL + B DJNZ TVADDLP1 ; Reset SP PUSH HL ; PUSH SP LD C,(HL) ; Push memory bytes on stack INC HL ; LD B,(HL) ; PUSH BC ; DEC HL ; ADJUST HL DEC HL ; DEC HL ; DEC HL ; PUSH HL ; SAVE IT ; "TV STORAGE DUMP Registers: A B C D E H L" LD HL,TITLEREGSMSG ; CALL TVPUTMSG ; POP HL ; Get back pointer CALL REGPRINT ; PUSH HL ; LD HL,ALTREGSMSG ; ALTERNATE REG SET CALL TVPUTMSG ; POP HL ; CALL REGPRINT ; EX DE,HL ; LD HL,FLAGSMSG ; FLAGS CALL TVPUTMSG ; LD B,0FH ; TVADDLP2: ; 003 110 0348H INC DE ; DE + B DJNZ TVADDLP2 ; CALL FLAGPRINT ; LD B,08H ; TVADDLP3: ; 003 120 DEC DE ; DE - B DJNZ TVADDLP3 ; CALL FLAGPRINT ; LD HL,INDEXMSG ; INDECES, I & R CALL TVPUTMSG ; LD B,07H ; LOAD B W 06H TVADDLP4: ; 003 136 035EH DEC DE ; DE - B DJNZ TVADDLP4 ; EX DE,HL ; CALL DUMPCHARSHORT ; CALL DUMPCHARSHORT ; LD B,03H ; CALL DUMPCHAR ; CALL DUMPCHARSHORT ; LD B,04H ; CALL DUMPCHAR ; LD B,05H ; CALL DUMPCHAR ; PUSH HL ; LD HL,STACKMSG ; STACK CALL TVPUTMSG ; POP HL ; CALL DUMPCHARSHORT ; CALL DUMPCHARSHORT ; LD B,03H ; CALL DUMPCHAR ; CALL DUMPCHARSHORT ; LD B,09H ; TVSPLP: ; 003 222 0392H CALL TVPUTSP ; DJNZ TVSPLP ; LD A,(INTLVL) ; CALL TVPUTMSG ; JP DUMPSTORAGE ; ; *************************************** ; Print register values from memory REGPRINT: ; 003 240 ; Print 1st byte LD E,(HL) ; Fetch 1st byte CALL OHPUTCH ; Print it DEC HL ; LD B,06H ; Do 6 more RPLP: ; 003 247 CALL TVPUTSP ; Space over DEC HL ; HL -= 1 CALL OHPRINTMEM ; Print (HL) as Oct / Hex DJNZ RPLP ; DEC HL ; For next dump routine RET ; Exit REGPRINT ; *************************************** ; Print flags from storage FLAGPRINT: ; 003 262 03B2H LD A,(DE) ; Fetch the flag byte CALL FLAGSHORT ; 03CEH CALL FLAGSHORT ; CALL FLAGLONG ; 03CDH CALL FLAGLONG ; CALL FLAGSHORT ; CALL FLAGSHORT ; LD B,03H ; FLAGSPLP: ; 003 307 CALL TVPUTSP ; DJNZ FLAGSPLP ; RET ; ; ************************************** ; FLAGLONG: ; 003 315 03CDH RLCA ; FLAGSHORT: ; 003 316 RLCA ; LD C,A ; SAVE DATA IN C AND A,01H ; ISOLATE BIT OR A,0B0H ; MAKE INTO ASCII '0' OR '1' CALL TVPUTCH ; PRINT ASCII in A CALL TVPUTSP ; PRINT SPACE LD A,C ; GET DATA BACK RET ; ; ********************************** ; PRINT SPACES (COUNT PASSED IN B) ; THEN PRINT MEMORY @ (HL); HL -= 1 DUMPCHAR: ; 003 334 03DCH CALL TVPUTSP ; DJNZ DUMPCHAR ; SPACE COUNT IN B DUMPCHARSHORT: ; 003 341 CALL OHPRINTMEM ; FETCH CHAR @ (HL) & PRINT DEC HL ; RET ; Exit DUMPCHAR ; ############################### IF PATCH1 ; ; Pointer Octal/Hex ; Dump & Program ; ; The patching instructions were: ; Replace bytes 003 346 - 004 377 ; Replace bytes 001 233 - 001 246 ; ; Move bytes from 005 225... to 005 124... ; ; If we are putting in the OS patch ; then use the following code BEGIN: ; 003 346 03E6H DUMPSTORAGE: LD SP,0200H ; LD HL,0000H ; PUSH HL ; ; Get operator command KEY: ; 003 355 03EDH CALL KBGETCH ; Get operator command AND 0DFH ; Mask LD D,A ; Save ; Check command entered. ; SPACE = next page, R = return to OS, H = set page ; L = set byte, PTEST: ; 003 363 03F3H CP 80H ; ASCII SPACE entered ? JR NZ,RTEST ; No, go look for an 'R' ; Space key entered, show a new page POP DE ; DUMP OLD HL JR DCONV ; RTEST: ; 003 372 03FAH POP HL ; CP 0D2H ; R = RETURN TO OS JP Z,OPMONITOR ; HTEST: ; 004 000 0400H CP 0C8H ; 'H' ? JR NZ,LTEST ; CALL HLOUT ; LD H,A ; JR DCONV ; LTEST: ; 004 012 040AH CP 0CCH ; 'L' ? JR NZ,STEST ; CALL HLOUT ; LD L,A ; Set byte in page JR DCONV ; ; RIGHT ARROW OR CTL L FOR SPACE RIGHT STEST: ; 004 024 0414H CP 08CH ; ^L ? JR NZ,BTEST ; INC HL ; JR DCONV ; ; LEFT ARROW OR CTL H FOR BACKSPACE BTEST: ; 004 033 041BH CP 88H ; ^H JR NZ,UTEST ; DEC HL ; JR DCONV ; UTEST: ; 004 042 0422H AND A ; CLEAR CARRY LD DE,0006H ; ; UP ARROW OR CONTROL K FOR LINE UP CP 8BH ; ^K ? JR NZ,DTEST ; SBC HL,DE ; JR DCONV ; ; DOWN ARROW, LINE FEED, OR CTL J FOR LF DTEST: ; 004 056 042EH CP 8AH ; ^J ? JR NZ,NTEST ; ADC HL,DE ; JR DCONV ; NTEST: ; 004 066 0436H OR 20H ; PUSH AF ; LD B,09H ; SKIP: ; 004 073 043BH CALL TVPUTSP ; DJNZ SKIP ; POP AF ; CALL ASCIIS ; LD (HL),A ; INC HL ; ; Display convert ? DCONV: ; 004 106 0446H PUSH HL ; CALL TVERASE ; 000 346 00E6H POP DE ; HL => DE PUSH DE ; BACK TO NORMAL LD H,D ; POINTER ON DISPLAYED PAGE LD A,E ; PAGE1: ; 004 116 044EH CP 5AH ; JR NC,PAGE2 ; LD L,00H ; JR PSTART ; PAGE2: ; 004 126 0456H CP 0B4H ; JR NC,PAGE3 ; LD L,5AH ; JR PSTART ; PAGE3: ; 004 136 045EH LD L,0B4H ; PSTART: ; 004 140 0460H LD E,H ; CALL OHPUTCH ; 002 106 0246H CHARACTER LD E,L ; CALL OHPUTCH ; 002 106 0246H CALL TVPUTSP ; 000 370 00F8H CALL TVPUTSP ; 000 370 00F8H LD B,006 ; BYTE: ; 004 160 0470H POP DE ; PUT STACK HL IN DE PUSH HL ; PUSH DE ; SBC HL,DE ; SEE IF POINTER HERE ? JR Z,POINTR ; CALL TVPUTSP ; 000 370 00F8H JR CONTIN ; POINTR: ; 004 174 047CH LD A,9AH ; CALL PUTC ; 000 372 00FAH CONTIN: ; 004 201 0481H POP DE ; POP HL ; PUSH DE ; LD E,(HL) ; Print memory contents. CALL OHPUTCH ; INC HL ; LD A,L ; CP 5AH ; JP Z,KEY ; CP 0B4H ; JP Z,KEY ; CP 00H ; JR NZ,NBYTE ; LD B,08H ; SKIP7: ; 004 232 049AH CALL TVPUTSP ; DJNZ SKIP7 ; JP KEY ; NBYTE: ; 004 242 04A2H GETC: DJNZ BYTE ; JR PSTART ; ASCII: ; 004 245 04A5H CALL KBGETCH ; KBD # ENTRY ASCIIS: ; 004 251 04A9H LD B,A ; LD A,(OHCONST) ; 001 247 04A7H HEXCK: ; 004 255 04ADH CP 'H' ; LD A,B ; JR Z,HEX ; OCTAL: ; 004 262 04B1H CALL PUTC ; 000 372 00FAH LD A,B ; RRCA ; RRCA ; AND 0C0H ; LD C,A ; CALL KBGETCH ; 001 250 01A8H LD B,A ; CALL PUTC ; 000 372 00FAH LD A,B ; RLCA ; RLCA ; RLCA ; AND 38H ; ADD C ; LD C,A ; CALL KBGETCH ; 001 250 01A8H LD B,A ; CALL PUTC ; 000 372 00FAH LD A,B ; AND 07H ; ADD C ; RET ; HEX: ; 004 326 04D6H CALL TVPUTSP ; 000 370 00F8H LD A,B ; CALL HEXERS ; 004 352 04EAH RLCA ; RLCA ; RLCA ; RLCA ; LD B,A ; CALL HEXER ; 004 347 04E7H ADD B ; RET ; HEXER: ; 004 347 04E7H CALL KBGETCH ; 001 250 01A8H HEXERS: ; 004 352 04EAH CP 0E0H ; JR C,UCASE ; 002 070 0238H SUB 20H ; UCASE: ; 004 360 04F0H PUSH AF ; CALL PUTC ; 000 372 00FAH POP AF ; CP 0BAH ; '9' + 1 OR 80H JR C,NUMBER ; SUB 07H ; Bias HEX alpha down NUMBER: ; 004 373 04FBH SUB 0B0H ; Ascii => Binary RET ; 004 375 04FDH ; ############################### ELSE ; Not patching - use original code ; *************************************** ; Dump memory to monitor a page at a time DUMPSTORAGE: ; 003 346 03E6H LD SP,TOS ; LD HL,0000H ; ; SEE WHAT THE OPERATOR WANTS TO DO: ; SPACE = DUMP ANOTHER PAGE ; S = set memory page to display ; P = PROGRAM MEMORY ; R = exit to monitor command loop DUMPSLP: ; 003 354 CALL KBGETCH ; A <= KBD ASCII AND A,0DFH ; Convert to uppercase CP A,80H ; SPACE ? JR Z,DUMPCONV ; Do another page CP A,0D3H ; S ? JR Z,PAGEPRESET ; Go set memory display page CP A,0D0H ; P ? JP Z,KEYBDPROG ; Go let operator poke new values CP A,0D2H ; R ? JP Z,OPMONITOR ; EXIT to monitor here JR DUMPSLP ; NOT VALID CODE ; ***************************************** ; Operator sets memory page to dump PAGEPRESET: ; 004 005 0405H LD HL,PAGEMSG ; "ENTER PAGE" CALL TVPUTMSG ; 0200H CALL ASCIICONV ; LD H,L ; LD L,00H ; ; **************************************** ; Dump a page of memory to the monitor DUMPCONV: ; 004 021 0411H CALL TVERASE ; DLINELP: ; 004 024 ; Print HL in Hex or Octal LD E,H ; CALL TVPUTCH ; Print ASCII in A LD E,L ; CALL TVPUTCH ; Print ASCII in A CALL TVPUTSP ; Space over CALL TVPUTSP ; LD B,06H ; DCHARLP: ; 004 044 0424H CALL TVPUTSP ; LD E,(HL) ; Print Mem at (HL) CALL OHPUTCH ; in Octal or Hex INC HL ; LD A,L ; See where we are on the page CP A,60H ; END OF 1ST TV PAGE? JR Z,DUMPSLP ; Yes CP A,0FEH ; END OF 2ND PAGE JR Z,DUMPSLP ; Yes CP A,00H ; END OR 3RD TV PAGE JR Z,DUMPSLP ; Yes DJNZ DCHARLP ; JR DLINELP ; ; **************************************** ; READ KEYBOARD AS OCTAL OR HEX: ; OHCONST DETERMINES DIGIT FORMAT ; B IS TEMP STORAGE, CHARS ARE BUILT IN C ; Binary value is returned in A ASCIICONV: ; 004 075 043DH CALL KBGETCH ; A <= KBD ASCII (1st char) ; ARE WE DOING OCTAL OR HEX ? ASCIICONVSHORT: ; 004 100 LD B,A ; SAVE A BRIEFLY LD A,(OHCONST) ; OCTAL HEX CONSTANT CP A,'H' + 80H ; DOING HEX ? LD A,B ; A <= KBD ASCII JR Z,ASCIIHEX ; DOING HEX ASCIIOCTAL: ; 004 111 0449H ; OCTAL - FETCH & PRINT 3 OCTAL DIGITS ; Enter with 1st (MS) octal char in A and B CALL TVPUTCH ; PRINT ASCII in A LD A,B ; RRCA ; RRCA ; AND A,0C0H ; LD C,A ; CALL KBGETCH ; A <= KBD ASCII (2nd char) LD B,A ; Save char CALL TVPUTCH ; PRINT ASCII in A LD A,B ; Restore char RLCA ; RLCA ; RLCA ; AND A,38H ; ADD A,C ; LD C,A ; CALL KBGETCH ; A <= KBD ASCII (3rd char) LD B,A ; CALL TVPUTCH ; PRINT ASCII in A LD A,B ; AND A,07H ; ADD A,C ; RET ; RETURN VALUE IN A ; *************************************** ; PRINT 2 HEX DIGITS ; Returns thru HEXLS, ; Enter with MS Hex digit in A and B ; Returns Binary value of HEX digits in B ASCIIHEX: ; 004 155 CALL TVPUTSP ; HEXMS: ; Convert MS hex digit LD A,B ; A <= MS nibble CALL HEXER ; Print A as hex RLCA ; Position LS nibble RLCA ; Strange code: The missing RLCA ; RLCA is at HEXLS JP HEXLS ; Go fetch LS hex digit ; and return in B ; ***************************************** ; Fetch one keyboard char, convert it to hex ; & Print it. ; ; Return it in A KBHEX: ; 004 172 047AH CALL KBGETCH ; A <= KBD ASCII ; ***************************************** ; Convert A to HEX & print HEXER: ; 004 175 047DH CP A,0E0H ; 'a' - 1 ? JR C,HAVEUPPER ; SUB 20H ; CONVERT TO UPPER CASE HAVEUPPER: ; 004 203 PUSH AF ; Save CALL TVPUTCH ; PRINT ASCII in A POP AF ; Restore CP A,0BAH ; A < ('9' + 1) + 80H ? JR C,NUM ; Its a number, branch ; Fall thru & process ALPHA SUB 07H ; Bias 'A' .. 'F' down NUM: ; 004 216 048EH SUB 0B0H ; RET ; ; *************************************** ; COMMAND. ; This is really a kbd poke program that allows the user ; to set values in memory in octal or hex notation. You ; can't change ROM, and playing around below 0600H risks ; crashing this OS. The default sandbox for playing around ; is the DEFAULTUSER area at 0600H. KEYBDPROG: ; 004 221 0491H LD HL,KBDPROGMSG ; "KEYBOARD PROGRAMMER" ; "ADDRESS:" CALL TVPUTMSG ; LD HL,DEFAULTUSER ; DEFAULT PROGRAMMING AREA XF4: ; 004 232 049AH ; Print value of HL LD E,H ; Pass byte in E CALL OHPUTCH ; Print LD E,L ;Same for L CALL OHPUTCH ; GETC: ; 004 242 04A2H CALL KBGETCH ; A <= KBD ASCII AND 0DFH ; CONVERT TO UPPER CASE CP 0C8H ; "H" + 80H ? JR NZ,XF3 ; NO ; Yes, fall thru CALL TVERASE ; LD A,'H' + 80H ; Echo CALL TVPUTCH ; PRINT ASCII in A CALL ASCIICONV ; LD H,A ; XF6: ; 004 267 04B7H CALL TVERASE ; JR XF4 ; XF3: ; 004 274 04BCH CP A,'L' + 80H ; JR NZ,XF5 ; CALL TVERASE ; LD A,'L' + 80H ; CALL TVPUTCH ; PRINT ASCII in A CALL ASCIICONV ; LD L,A ; JR XF6 ; XF5: ; 004 316 04CEH ; Check for 'S' or 'R' input CP A,'S' + 80H ; 'S' ? STORAGE DUMP JP Z,TVDUMP ; CP A,'R' + 80H ; 'R' ? RETURN TO OP MONITOR JP Z,OPMONITOR ; ; Not an 'S' or 'R' entry OR 20H ; PUSH AF ; LD B,08H ; XF7: ; 004 335 04DDH DEC HL ; This is basically a subtract DJNZ XF7 ; HL -= 8 CALL TVERASE ; LD B,08H ; XF8: ; 004 345 04E5H CALL HLLIST ; CALL MEMLIST ; INC HL ; DJNZ XF8 ; CALL HLLIST ; POP AF ; CALL ASCIICONVSHORT ; LD (HL),A ; CALL SPACES20 ; Prints 20 spaces INC HL ; CALL HLLIST ; JP PUTQUES ; Print '?' ENDIF ; Putting in OS patch ; ############################### ORG 0500H ; OPMON MUST BE HERE ; ****************************************** ; This is the main OS command loop. ; Come here to begin OS operations. ; ; Set stack & int mode, turn interrupts on. ; Show the menu of operator commands. ; Accept & validate a menu selection. ; Adjust number base to HEX or OCTAL if necessary. ; Look up command handler address from vector table. ; Go and execute code to handle operator's request. OPMONITOR: ; 005 000 0500H LD SP,TOS ; SET STACK IM 0 ; 8080 INT MODE LD A,'0' + 80H ; '0' <<<< Nothing else seems to check or LD (INTLVL),A ; modify INTLVL, but it is displayed. EI ; INTERRUPTS ON LD HL,OPTIONSMENU ; All the things we can do CALL TVPUTMSG ; Show the operator GETNUM: ; 005 021 0511H CALL KBGETCH ; A <= KBD ASCII ; Validate numeric value: Reject < 0 & > 9 CP 0BAH ; A > '9' + 80H ? JR NC,GETNUM ; Oops, > 9 CP 0B0H ; A < '0' + 80H ? JR C,GETNUM ; Oops, < 0 ; Fall thru to process menu selection ; WARNING: Tricky code ahead ; We have an ASCII menu selection # in A ; 0 <= # <= 9 ; ; Translate this to an absolute address in the command vector table ; at 0540H. We are translating the DG ASCII menu selection into the ; LSB of the table address here. ; ; I have never seen it done this way before. The conventional approach ; would be to point HL at the command table, add in the offset from the ; ASCII menu selection translated to binary, Load up DE with the table ; address, swap DE with HL and jump to (HL). In this code the table is nailed ; down to 0540H forever. My approach takes 11 bytes minimum, whereas ; Dr. Bob takes 3. ; ; This is very fast, subtle, and fragile code. Too clever by half for ; my taste. But it works ! ; ; This is the translation code; ASCII to table addr. RLCA ; * 2 for 2 bytes per address AND 5EH ; Mask for table @ 0540H ; This is a walk through of the possible inputs & the translation ; DG ASCII in Item Translation in A ; '0' USER => 40H ; '1' READ => 42H ; '2' WRITE => 44H ; '3' OCTDUMP => 46H ; '4' OCTPGM => 48H ; '5' HEXDUMP => 4AH ; '6' HEXPGM => 4CH ; '7' USER => 4EH ; '8' USER => 50H ; '9' USER => 52H ; ; We only set up the LSB of the LD HL,xxxx command ; The MSB is already 05H. LD (JPVECTOR),A ; Computed jump vector LS byte ; Is this user selection 0, 1, or 2 ? CP 46H ; LT '3' - Octal Dump JR C,COMPUTEDJP ; Don't change number base ; Is this a user selection, 7, 8, or 9 ? CP 4EH ; GTEQ '7' JR NC,COMPUTEDJP ; Yes, don't change number base ; Check how the user wants to see the data CP 4AH ; GTEQ Hex dump or pgm ? JR NC,SETHEX ; Yes, branch & set HEX XOR A ; No, Set OCTAL mode JR SETOCT ; ; Set the default to HEX, base 16 SETHEX: ; 005 061 0531H LD A,'H' + 80H ; 'H' + 80H ; Set the default to OCTAL, base 8 SETOCT: ; 005 063 0533H LD (OHCONST),A ; This flag sets I/O in OCTAL or HEX ; ********************************** ; <<<<< COMPUTED VECTOR HERE >>>>> ; Technically, this is self modifying code, which is ; frowned upon these days... for good reason. COMPUTEDJP: ; 005 066 0536H ; Load HL with computed jump address. ; The address we computed corresponds to one of the ; vectors in the command table. So, load HL with the ; address in the command table corresponding to the ; operator's menu choice. DB 2AH ; OPCODE FOR LD HL,nnnn JPVECTOR: DB 00H ; LSB OF VECTOR <= This is the byte we modify DB 05H ; MSB OF VECTOR ; We now have the address to jump to in HL ; Erase screen & take jump. CALL TVERASE ; Clear screen ; Here we jump to the address from the command table JP (HL) ; EXIT to computed address ; ********************************** ; DB 00H ; These are padding bytes to DB 00H ; position the vector table DB 00H ; at 0540H exactly ; ; The operation of the code depends on this table being at 0540H ; The Label is not actually referenced anywhere. Absolute memory ; locations are used. ; ; Address 0000H (In EPROM) is the restart location. It checks ; if the OS is present by looking for the signature bytes. If ; it finds them, it jumps into the OS command loop. Otherwise, ; it prompts the operator to load the OS from cassette. So no ; harm is done by jumping there. You either re-load or you ; wind up back at a menu prompt. ; ; Note: Vector 0 is not displayed in the options menu, ; but it exists ! IF PATCH1 ; If we are patching the OS CMDVECTORTBL: DW 0000H ; 005 100 0540H - 0 USER SET DW STARTREAD ; 005 102 0542H - 1 READ DW WRITE2K ; 005 104 0544H - 2 WRITE DW DUMPSTORAGE ; 005 106 0546H - 3 OCTAL PROGRAM DW DUMPSTORAGE ; 005 110 0548H - 4 HEX PROGRAM DW 0000H ; 005 112 054AH - 5 USER SET DW 0000H ; 005 114 054CH - 6 USER SET DW 0000H ; 005 116 054EH - 7 USER SET DW 0000H ; 005 120 0550H - 8 USER SET DW 0000H ; 005 122 0552H - 9 USER SET ELSE ; Use old code CMDVECTORTBL: DW 0000H ; 005 100 0540H - 0 USER SET DW STARTREAD ; 005 102 0542H - 1 READ DW WRITE2K ; 005 104 0544H - 2 WRITE DW TVDUMP ; 005 106 0546H - 3 OCTALDUMP DW KEYBDPROG ; 005 110 0548H - 4 OCTAL PROGRAM DW TVDUMP ; 005 112 054AH - 5 HEXDUMP DW KEYBDPROG ; 005 114 054CH - 6 HEX PROGRAM DW 0000H ; 005 116 054EH - 7 USER SET DW 0000H ; 005 120 0550H - 8 USER SET DW 0000H ; 005 122 0552H - 9 USER SET ENDIF ; Patching ; ********************************** ; Print DG ASCII in A PUTC: ; 005 124 0554H CALL TVPUTCH ; PRINT ASCII in A JP GETC ; ; ********************************** ; MEMLIST: ; 005 132 055AH LD E,(HL) ; Print memory @ (HL) CALL OHPUTCH ; Pass byte to print in E JR SPACES3 ; JR 0CH ; ********************************** ; HLLIST: ; 005 140 0560H LD E,H ; PRINT HL itself CALL OHPUTCH ; LD E,L ; CALL OHPUTCH ; fall thru ; ********************************** ; Print 3 spaces SPACES3: ; 005 150 0568H LD E,03H ; print 3 spaces JR SPACER ; JR 02H ; ********************************** ; Print 20 spaces SPACES20: ; 005 154 056CH ; 14H == 20D == 24Octal LD E,14H ; ; ********************************** ; Print spaces for count in E SPACER: ; 005 156 056EH CALL TVPUTSP ; DEC E ; JR NZ,SPACER ; JR NZ,FAH RET ; ; ************************************** ; KBDPROGMSG: ; 005 165 0575H DB 0FFH ; HOME & ERASE DB 26H ; SPACES DB 'K' + 80H ; 'KEYBOARD PROGRAMMER' ; DB 'E' + 80H ; DB 'Y' + 80H ; DB 'B' + 80H ; DB 'O' + 80H ; DB 'A' + 80H ; DB 'R' + 80H ; DB 'D' + 80H ; DB ' ' + 80H ; DB 'P' + 80H ; DB 'R' + 80H ; DB 'O' + 80H ; DB 'G' + 80H ; DB 'R' + 80H ; DB 'A' + 80H ; DB 'M' + 80H ; DB 'M' + 80H ; DB 'E' + 80H ; DB 'R' + 80H ; DB 67H ; SPACES DB 'A' + 80H ; 'Address:' DB 'd' + 80H ; DB 'd' + 80H ; DB 'r' + 80H ; DB 'e' + 80H ; DB 's' + 80H ; DB 's' + 80H ; DB ':' + 80H ; DB 02H ; SPACES DB 00 ; RETURN IF PATCH1 ; IF WE ARE PATCHING THE OS ORG 0554H ; MOVE THIS TO CODE DOWN ENDIF OPTIONSMENU: ; 005 225 0595H DB 0FFH ; HOME ERASE DB 'Z' + 80H ; 'Z-80 OP SYS OPTIONS: ' DB '-' + 80H ; DB '8' + 80H ; DB '0' + 80H ; DB ' ' + 80H ; DB 'O' + 80H ; DB 'P' + 80H ; DB ' ' + 80H ; DB ' ' + 80H ; DB 'S' + 80H ; DB 'Y' + 80H ; DB 'S' + 80H ; DB ' ' + 80H ; DB 'O' + 80H ; DB 'P' + 80H ; DB 'T' + 80H ; DB 'I' + 80H ; DB 'O' + 80H ; DB 'N' + 80H ; DB 'S' + 80H ; DB ':' + 80H ; DB ' ' + 80H ; DB '1' + 80H ; '1 READ ' 005 254 05ACH DB ' ' + 80H ; DB 'R' + 80H ; DB 'E' + 80H ; DB 'A' + 80H ; DB 'D' + 80H ; DB ' ' + 80H ; DB '2' + 80H ; '2 WRITE ' 005 263 05B3H DB ' ' + 80H ; DB 'W' + 80H ; DB 'R' + 80H ; DB 'I' + 80H ; DB 'T' + 80H ; DB 'E' + 80H ; DB ' ' + 80H ; DB '3' + 80H ; '3 OCTAL DUMP ' 005 273 05BBH DB ' ' + 80H ; DB 'O' + 80H ; DB 'C' + 80H ; DB 'T' + 80H ; DB 'A' + 80H ; DB 'L' + 80H ; DB ' ' + 80H ; DB 'D' + 80H ; DB 'U' + 80H ; DB 'M' + 80H ; DB 'P' + 80H ; DB ' ' + 80H ; DB '4' + 80H ; '4 OCTAL PROGRAM ' 005 310 05C8H DB ' ' + 80H ; DB 'O' + 80H ; DB 'C' + 80H ; DB 'T' + 80H ; DB 'A' + 80H ; DB 'L' + 80H ; DB ' ' + 80H ; DB 'P' + 80H ; DB 'R' + 80H ; DB 'O' + 80H ; DB 'G' + 80H ; DB 'R' + 80H ; DB 'A' + 80H ; DB 'M' + 80H ; DB ' ' + 80H ; DB '5' + 80H ; '5 HEX DUMP ' 005 330 05D8H DB ' ' + 80H ; DB 'H' + 80H ; DB 'E' + 80H ; DB 'X' + 80H ; DB ' ' + 80H ; DB 'D' + 80H ; DB 'U' + 80H ; DB 'M' + 80H ; DB 'P' + 80H ; DB ' ' + 80H ; DB '6' + 80H ; '6 HEX PROGRAM ' 005 343 05E3H DB ' ' + 80H ; DB 'H' + 80H ; DB 'E' + 80H ; DB 'X' + 80H ; DB ' ' + 80H ; DB 'P' + 80H ; DB 'R' + 80H ; DB 'O' + 80H ; DB 'G' + 80H ; DB 'R' + 80H ; DB 'A' + 80H ; DB 'M' + 80H ; DB 00H ; RETURN 005 360 05F0H ; NOTE: SPACES IS # OF SPACES TO PRINT TO END OF LINE ; LINE + SPACES MUST TOTAL 40 ; ************************************* ; ; DS 05FFH - $ ; ORG 0600H ; DEFAULTUSER: EQU $ ; ; DEFAULT USER PROGRAMMING AREA, ONE PAGE FROM ; 0600H TO 07FFH DS 07FFH - $ ; TAPE LOADS FROM 0100H TO 07FFH FINIS: EQU $ ; END