home *** CD-ROM | disk | FTP | other *** search
- INTERRUPTS SEGMENT AT 0H ;This is where the keyboard interrupt
- ORG 9H*4 ;holds the address of its service routine
- KEYBOARD_INT LABEL WORD
- ORG 21H*4 ;holds the address of its service routine
- DOS_INT LABEL WORD
- INTERRUPTS ENDS
-
- SCREEN SEGMENT AT 0B000H ;A dummy segment to use as the
- SCREEN ENDS ;Extra Segment
-
- ROM_BIOS_DATA SEGMENT AT 40H ;BIOS statuses held here, also keyboard buffer
-
- ORG 1AH
- HEAD DW ? ;Unread chars go from Head to Tail
- TAIL DW ?
- BUFFER DW 16 DUP (?) ;The buffer itself
- BUFFER_END LABEL WORD
-
- ROM_BIOS_DATA ENDS
-
- CODE_SEG SEGMENT
- ASSUME CS:CODE_SEG
- ORG 100H ;ORG = 100H to make this into a .COM file
- FIRST: JMP LOAD_PAD ;First time through jump to initialize routine
-
- COPY_RIGHT DB '(C)1987 S Holzner'
- INT21 LABEL DWORD ;Point to next two words for jump.
- OLD_DOS_INT DW 2 DUP(?) ;Store original DOS INT21 address here.
- FIRST_FLAG DB 1 ;First time through? Get COMMAND address
- COMMAND_ADDR DW ? ;Store IP of calling routine in COMMAND.
- OLD_DS DW 1 ;Keep DS:DX of old keyboard buffer.
- OLD_DX DW 1001H
- KEY1 DB 'SAVE', 0DH
- KEY2 DB 'save', 0DH
- KEY3 DB 'Save'
- CR DB 0DH,0AH,'$' ;Use this <cr> to send to DOS.
- FILE_DONE DB 0DH,0AH,'PAD.TXT created.',0DH,0AH,'$'
- CNTRL_N_FLAG DW 0 ;Cntrl-N on or off
- FILENAME DB 'PAD.TXT',0
- PAD_CURSOR DW 0 ;Current position in pad
- CURSOR_STORAGE DW 0,600,1200,1800,2400 ;Hold cursor each page.
- PAD_OFFSET DW 0 ;Chooses 1st 250 bytes or 2nd
- PAD_BEGIN DW 0 ;Beginning of current page.
- PAD_END DW 599 ;End of current page.
- PAGE_NUMBER DW 0 ;Page Number 0-4.
- FIRST_POSITION DW ? ;Position of 1st char on screen
- ATTRIBUTE DB 112 ;Pad Attribute: 1EH better for color screens
- FORE_ATTR DB 0
- BACK_ATTR DB 0
- SCREEN_SEG_OFFSET DW 0 ;0 for mono, 8000H for graphics
- IO_CHAR DW ? ;Holds addr of Put or Get_Char
- STATUS_PORT DW ? ;Video controller status port
- OLD_KEY_INT LABEL WORD
- OLD_KEYBOARD_INT DD ? ;Location of old kbd interrupt
-
- NEWPAD PROC NEAR ;The keyboard interrupt will now come here.
- ASSUME CS:CODE_SEG
- PUSH AX ;Save the used registers for good form
- PUSH BX
- PUSH CX
- PUSH DX
- PUSH DI
- PUSH SI
- PUSH DS
- PUSH ES
- PUSHF ;First, call old keyboard interrupt
- CALL OLD_KEYBOARD_INT
-
- ASSUME DS:ROM_BIOS_DATA ;Examine the char just put in
- MOV BX,ROM_BIOS_DATA
- MOV DS,BX
-
- MOV BX,TAIL ;Point to current tail
- CMP BX,HEAD ;If at head, kbd int has deleted char
- JE IN ;So leave
- SUB BX,2 ;Point to just read in character
- CMP BX,OFFSET BUFFER ;Did we undershoot buffer?
- JAE NO_WRAP ;Nope
- MOV BX,OFFSET BUFFER_END ;Yes -- move to buffer top
- SUB BX,2 ;Point to just read in characterqqq
- NO_WRAP:MOV DX,[BX] ;Char in DX now
- CMP DX,310EH ;Is the char a Cntrl-N?
- JNE NOT_CNTRL_N ;No
- MOV TAIL,BX ;Yes -- delete it from buffer
- NOT CNTRL_N_FLAG ;Switch Modes
- CMP CNTRL_N_FLAG,0 ;Cntrl-N off?
- JNE CNTRL_N_ON ;No, only other choice is on
- CNTRL_N_OFF:
- LEA DX,PAD
- MOV PAD_OFFSET,DX
- ADD PAD_OFFSET,3000
- LEA AX,PUT_CHAR ;Make IO call Put_Char as it scans
- MOV IO_CHAR,AX ;over all locations in pad on screen
- CALL IO ;Restore screen
- IN: JMP OUT ;Done
- CNTRL_N_ON:
- LEA DX,PAD
- MOV PAD_OFFSET,DX
- ADD PAD_OFFSET,3000
- LEA AX,GET_CHAR ;Make IO use Get_char so current screen
- MOV IO_CHAR,AX ;is stored
- CALL IO ;Store Screen
- CALL DISPLAY ;And put up the pad
- JMP OUT ;Done here.
- NOT_CNTRL_N:
- TEST CNTRL_N_FLAG,1 ;Is Cntrl-N on?
- JZ IN ;No -- leave
- MOV TAIL,BX ;Yes, delete this char from buffer
- CMP DX,5300H ;Decide what to do -- is it a Delete?
- JNE RUBOUT_TEST ;No -- try Rubout
- PUSH DS
- PUSH CS
- POP DS
- MOV BX,PAD_END
- DEC BX
- DEL_LOOP:
- MOV BYTE PTR [BX],' ' ;Move space to current pad position
- DEC BX ;and go back one
- CMP BX,PAD_BEGIN
- JNZ DEL_LOOP ;until done.
- MOV BYTE PTR [BX],'_' ;Put the cursor at the beginning
- MOV DX,PAD_BEGIN
- MOV PAD_CURSOR,dx ;qq ;And start cursor over
- POP DS
- CALL DISPLAY ;Put up the new pad on screen
- JMP OUT ;And take our leave
- RUBOUT_TEST:
- CMP DX,0E08H ;Is it a Rubout?
- JNE CRLF_TEST ;No -- try carriage return-line feed
- PUSH DS
- PUSH CS
- POP DS
- MOV BX,PAD_CURSOR ;Yes -- get current pad location
- CMP BX,PAD_BEGIN ;Are we at beginning?
- JLE NEVER_MIND ;Yes -- can't rubout past beginning
- MOV BYTE PTR [BX-1],'_' ;And move cursor back one
- DEC PAD_CURSOR ;Set the pad location straight
- CMP BX,PAD_END ;Save page number.
- JE NEVER_MIND
- MOV BYTE PTR [BX],' ' ;No -- move space to current position
- NEVER_MIND:
- POP DS
- CALL DISPLAY ;And put the result on the screen
- JMP OUT ;Done here.
- CRLF_TEST:
- CMP DX,1C0DH ;Is it a carriage return-line feed?
- JNE PGUP_TEST ;No
- PUSH DS
- PUSH CS
- POP DS
- CALL CRLF ;Yes -- move to next line
- POP DS
- CALL DISPLAY ;And display result on screen
- JMP OUT ;Done.
- PGUP_TEST:
- CMP DX,4900H
- JNE PGDN_TEST
- CMP PAGE_NUMBER,0
- JNE DEC_PAGE
- JMP OUT
- DEC_PAGE:
- MOV BX,PAGE_NUMBER ;STORE PAD CURSOR
- ADD BX,BX
- MOV CX,PAD_CURSOR
- MOV CURSOR_STORAGE[BX],CX
- DEC PAGE_NUMBER
- SUB BX,2
- MOV CX,CURSOR_STORAGE[BX]
- MOV PAD_CURSOR,CX
-
- MOV AX,PAGE_NUMBER
- MOV BX,600
- MUL BX
- LEA DX,PAD
- ADD AX,DX
- MOV PAD_BEGIN,AX
- ADD AX,599
- MOV PAD_END,AX
- CALL DISPLAY
- JMP OUT
- PGDN_TEST:
- CMP DX,5100H
- JNE F1_TEST
- CMP PAGE_NUMBER,4
- JNE INC_PAGE
- JMP OUT
- INC_PAGE:
- MOV BX,PAGE_NUMBER ;Store pad cursor.
- ADD BX,BX
- MOV CX,PAD_CURSOR
- MOV CURSOR_STORAGE[BX],CX
- INC PAGE_NUMBER
- ADD BX,2
- MOV CX,CURSOR_STORAGE[BX]
- MOV PAD_CURSOR,CX
- MOV AX,PAGE_NUMBER
- MOV BX,600
- MUL BX
- LEA DX,PAD
- ADD AX,DX
- MOV PAD_BEGIN,AX
- ADD AX,599
- MOV PAD_END,AX
- CALL DISPLAY
- JMP OUT
- F1_TEST:CMP DX,3B00H
- JNE F2_TEST
- MOV AH,FORE_ATTR
- INC AH
- CMP AH,16
- JL OKFORE
- MOV AH,0
- OKFORE: MOV FORE_ATTR,AH
- AND ATTRIBUTE,240 ;Clear fore color
- OR ATTRIBUTE,AH
- CALL DISPLAY
- JMP OUT
- F2_TEST:CMP DX,3C00H
- JNE CHAR_TEST
- MOV AH,BACK_ATTR
- ADD AH,16
- CMP AH,120
- JB OKBACK
- MOV AH,0
- OKBACK: MOV BACK_ATTR,AH
- AND ATTRIBUTE,15 ;Clear back color
- OR ATTRIBUTE,AH
- CALL DISPLAY
- JMP OUT
- CHAR_TEST:
- PUSH DS
- PUSH CS
- POP DS
- MOV BX,PAD_CURSOR ;Get current pad location
- CMP BX,PAD_END ;Are we past the end of the pad?
- JGE PAST_END ;Yes -- throw away char
- MOV byte ptr [bx],DL ;No -- move ASCII code into pad
- INC PAD_CURSOR ;Increment pad location
- INC BX
- CMP BX,PAD_END
- JE PAST_END
- MOV BYTE PTR [BX],'_' ;Advance cursor
- PAST_END:
- POP DS
- CALL DISPLAY ;Put result on screen
- OUT: POP ES ;Having done Pushes, here are the Pops
- POP DS
- POP SI
- POP DI
- POP DX
- POP CX
- POP BX
- POP AX
- IRET ;An interrupt needs an IRET
- NEWPAD ENDP
-
- DISPLAY PROC NEAR ;Puts the whole pad on the screen
- PUSH AX
- PUSH PAD_BEGIN
- POP PAD_OFFSET
- LEA AX,PUT_CHAR ;Make IO use Put-Char so it does
- MOV IO_CHAR,AX
- CALL IO ;Put result on screen
- POP AX
- RET ;Leave
- DISPLAY ENDP
-
- CRLF PROC NEAR ;This handles carriage returns
- MOV DI,PAD_END ;Are we on last line?
- SUB DI,40
- CMP PAD_CURSOR,DI
- JGE DONE ;Yes, can't do a carriage return, exit
- NEXT_CHAR:
- MOV BX,PAD_CURSOR ;Get pad location
- MOV AX,BX ;Get another copy for destructive tests
- SUB AX,PAD_BEGIN
- EDGE_TEST:
- CMP AX,39 ;Are we at the edge of the pad display?
- JE AT_EDGE ;Yes -- fill pad with new cursor
- JL ADD_SPACE ;No -- Advance another space
- SUB AX,40 ;Subtract another line-width
- JMP EDGE_TEST ;Check if at edge now
- ADD_SPACE:
- MOV BYTE PTR [BX],' ' ;Add a space
- INC PAD_CURSOR ;Update pad location
- JMP NEXT_CHAR ;Check if at edge now
- AT_EDGE:
- MOV BYTE PTR [BX],' '
- MOV BYTE PTR [BX+1],'_' ;Put cursor in next location
- INC PAD_CURSOR ;Update pad location to new cursor
- DONE: RET ;And out.
- CRLF ENDP
-
- GET_CHAR PROC NEAR ;Gets a char from screen and advances position
- PUSH DS
- PUSH DX
- PUSH CS
- POP DS
-
- MOV SI,2 ;Loop twice, once for char, once for attribute
- MOV DX,STATUS_PORT ;Get ready to read video controller status
-
- G_WAIT_LOW: ;Start waiting for a new horizontal scan -
- IN AL,DX ;Make sure the video controller scan status
- TEST AL,1 ;is low
- JNZ G_WAIT_LOW
- G_WAIT_HIGH: ;After port has gone low, it must go high
- IN AL,DX ;before it is safe to read directly from
- TEST AL,1 ;the screen buffer in memory
- JZ G_WAIT_HIGH
-
- MOV AH,ES:[DI] ;Do the move from the screen, one byte at a time
- INC DI ;Move to next screen location
- DEC SI ;Decrement loop counter
- CMP SI,0 ;Are we done?
- JE LEAVE ;Yes
- MOV BYTE PTR [BX],AH ;No -- put char we got into the pad
- JMP G_WAIT_LOW ;Do it again
- LEAVE: INC BX
- MOV BYTE PTR [BX],AH
- INC BX ;Update pad location
- POP DX
- POP DS
- RET
- GET_CHAR ENDP
-
- PUT_CHAR PROC NEAR ;Puts one char on screen and advances position
- PUSH DS
- PUSH CX
- PUSH DX
- PUSH CS
- POP DS
- MOV AH,BYTE PTR [BX] ;Get the char to be put onto the screen
- MOV SI,2 ;Loop twice, once for char, once for attribute
- MOV DX,STATUS_PORT ;Get ready to read video controller status
- P_WAIT_LOW: ;Start waiting for a new horizontal scan -
- IN AL,DX ;Make sure the video controller scan status
- TEST AL,1 ;is low
- JNZ P_WAIT_LOW
- P_WAIT_HIGH: ;After port has gone low, it must go high
- IN AL,DX ;before it is safe to write directly to
- TEST AL,1 ;the screen buffer in memory
- JZ P_WAIT_HIGH
- MOV ES:[DI],AH ;Move to screen, one byte at a time
-
- LEA CX,PAD
- ADD CX,3000
- CMP PAD_OFFSET,CX
- JNE GET_ATT ;We are restoring pad here.
- MOV AH,BYTE PTR [BX+1]
- JMP SHORT INCDI
-
- GET_ATT:MOV AH,ATTRIBUTE ;Load attribute byte for second pass
- INCDI: INC DI ;Point to next screen postion
- DEC SI ;Decrement loop counter
- JNZ P_WAIT_LOW ;If not zero, do it one more time
- INC BX ;Point to next char in pad
- LEA CX,PAD
- ADD CX,3000
- CMP PAD_OFFSET,CX
- JNE RETRN
- INC BX
- RETRN: POP DX
- POP CX
- POP DS
- RET ;Exeunt
- PUT_CHAR ENDP
-
- IO PROC NEAR ;This scans over all screen positions of the pad
- ASSUME ES:SCREEN ;Use screen as extra segment
- MOV BX,SCREEN
- MOV ES,BX
- MOV DI,SCREEN_SEG_OFFSET ;DI will be pointer to screen postion
- ADD DI,FIRST_POSITION ;Add width of screen minus pad width
- MOV BX,PAD_OFFSET ;BX will be pad location pointer
- MOV CX,15 ;There will be 10 lines
- LINE_LOOP:
- MOV DX,40 ;And 25 spaces across
- CHAR_LOOP:
- CALL IO_CHAR ;Call Put-Char or Get-Char
- DEC DX ;Decrement character loop counter
- JNZ CHAR_LOOP ;If not zero, scan over next character
- ADD DI,FIRST_POSITION ;Add width of screen minus pad width
- LOOP LINE_LOOP ;And now go back to do next line
- RET ;Finished
- IO ENDP
-
- DOS_WATCH PROC FAR ;The DOS interrupt will now come here.
- PUSH ES ;Save all used registers.
- PUSH DS
- PUSH BP
- PUSH AX
- PUSH BX
- PUSH CX
- CMP AH,0AH ;Is this the DOS Service we want to
- JE GO ; intercept?
- JMP OUT2 ;No.
- GO: MOV BX,DX ;Yes. Get length of original buffer.
- MOV CL,BYTE PTR DS:[BX]
- PUSH DS ;Save DS:DX, address of original buffer.
- ASSUME DS:CODE_SEG
- PUSH CS ;Make DS=CS to use local labels.
- POP DS
- POP OLD_DS
- PUSH DX
- POP OLD_DX
- MOV BX,80H ;We will use DS:80H for our buffer.
- MOV BYTE PTR DS:[BX],CL ;Store legal length from original buff.
- MOV BP,SP ;Prepare to get IP of return address.
- CMP FIRST_FLAG,1 ;First time through?
- JNE NOT_FIRST ;No -- check if COMMAND.COM is calling.
- MOV BX,SS:[BP+4] ;Yes, SHORTHND.COM must have just ended,
- MOV COMMAND_ADDR,BX ; so we are at monitor level -- get
- MOV FIRST_FLAG,0 ; calling addr in COMMAND.COM from stack
- PUSH AX
- PUSH CX
- PUSH DI
- PUSH ES
-
- PUSH CS
- POP ES
- LEA DI,PAD
- MOV CX,3000
- MOV AL,' '
- REP STOSB
- LEA DI,PAD
- MOV AL,'1'
- MOV CX,5
- LLOOP: MOV BYTE PTR [DI],'_'
- MOV [DI+599],AL
- INC AL
- ADD DI,600
- LOOP LLOOP
-
- POP ES
- POP DI
- POP CX
- POP AX
-
- JMP INTERCEPT ;Since we are at monitor level, intercept.
- NOT_FIRST: ;Not the first time through, check COMMAND addr.
- MOV BX,SS:[BP+4] ;Get ret addr from stack.
- CMP BX,COMMAND_ADDR ;Compare to what we know is COMMAND.COM
- JE INTERCEPT ;If not equal, not at monitor level.
- JMP OUT2 ;If not equal, not at monitor level.
- INTERCEPT: ;We are at monitor level, check for keys being typed.
- MOV DX,80H ;Get typein to OUR buffer instead of COMMAND's.
- MOV AH,0AH ;Use Service 0AH.
- PUSHF ;CALL INT 21 (we would intercept and INT 21 instruction)
- CALL INT21
- PUSHF ;Save flags.
- CLD ;Set upward flag for string commands.
- PUSH CS ;Set ES to CODE_SEG.
- POP ES
-
- LEA DI,KEY1 ;Start by checking for KEY1.
- MOV BP,DI ;BP will hold address of current KEY.
- MOV AX,3 ;Loop over 3 keys.
- CMPLOOP:MOV SI,82H ;Point to the read-in string.
- MOV BX,81H ;Get its length.
- XOR CX,CX ;Use CX as counted for REPE.
- MOV CL,BYTE PTR [BX]
- CMP CL,0 ;If nothing typed, skip the checking.
- JNG QIK
- CMP CL,4 ;If more than 4 characters typed, skip also.
- JG QIK
- REPE CMPSB ;Compare type-in to key.
- JNZ NEXT ;If zero flag not set, last char didn't match.
- JCXZ MAYBE ;All chars matched. Was it the right length?
- JMP SHORT NEXT
- MAYBE: CMP BYTE PTR [DI],0DH ;If next char in key is <cr>, end of key, so
- JE FOUND ;typed-in string was the right length.
-
- NEXT: ADD BP,5 ;Point to next key.
- MOV DI,BP ;Fill DI, which changes in REPE CMPSB, from BP.
- DEC AX ;BP, unlike DI, will always hold key addr.
- JNZ CMPLOOP ;If AX is 0, have checked all keys.
- JMP SHORT QIK
- ;SEND <CR> AND WRITE FILE - 40 BYTES, THEN <CR><LF> AT A TIME.
- FOUND: MOV AH,9
- LEA DX,CR ;First send a <CR><LF> to monitor.
- PUSHF
- CALL INT21
-
- LEA BP,CR
- MOV AH,3CH
- LEA DX,FILENAME
- MOV CX,0
- PUSHF
- CALL INT21
- MOV CX,75
- MOV BX,AX ;Get file handle in BX.
- LEA DX,PAD
- FILE_LOOP:
- MOV AH,40H
- PUSH CX
-
- MOV CX,40
- PUSHF
- CALL INT21 ;Write one line.
- PUSH DX
- LEA DX,CR
- MOV CX,2
- MOV AH,40H
- PUSHF
- CALL INT21 ;Write <CR><LF>
- POP DX
- ADD DX,40
- POP CX
- LOOP FILE_LOOP
-
- MOV AH,3EH
- PUSHF
- CALL INT21
- MOV AH,9
- LEA DX,FILE_DONE
- PUSHF
- CALL INT21
-
- POPF
- JMP SHORT SENDCR
-
- QIK: MOV BP,82H-5 ;No match, point to typed in command.
- ;FOUND: POPF ;If there was a match, add 5 to BP to get command addr.
- POPF ;If there was a match, add 5 to BP to get command addr.
- ADD BP,5
- SENDCR: PUSH OLD_DS ;Now use MOVSB to move command to COMMAND buffer
- POP ES
- MOV DI,OLD_DX ;Get DX of DS:DX.
- ADD DI,2 ;Point to where type-in is to go.
- MOV SI,BP
- MOV AL,0 ;AL will hold char count.
- FILL: MOVSB ;Move char to COMMAND.
- CMP BYTE PTR [SI-1],0DH ;Reached the command's end?
- JE FINFIL ;Yes.
- INC AL ;No, inc char count.
- JMP FILL ;Loop again.
- FINFIL: MOV DI,OLD_DX ;Done will string move.
- INC DI ;Give COMMAND char count in its buffer.
- MOV BYTE PTR ES:[DI],AL
- POP CX ;The POPs.
- POP BX
- POP AX
- POP BP
- POP DS
- POP ES
- IRET ;Finish with IRET.
- OUT2: POP CX ;The POPs for the case where we don't
- POP BX ; handle Service 0AH.
- POP AX
- POP BP
- POP DS
- POP ES
- ASSUME DS:NOTHING
- JMP INT21 ;Let INT 21H take over.
- DOS_WATCH ENDP
-
- PAD LABEL BYTE
-
- LOAD_PAD PROC NEAR ;This procedure intializes everything
- ASSUME DS:ROM_BIOS_DATA ;Examine the char just put in
- MOV BX,ROM_BIOS_DATA
- MOV DS,BX
- LEA DX,PAD
- MOV PAD_BEGIN,DX
- MOV PAD_CURSOR,DX
- MOV PAD_OFFSET,DX
- MOV CX,DX
- ADD CX,599
- MOV PAD_END,CX
- MOV CX,5
- MOV BX,0
- CLOOP: MOV CURSOR_STORAGE[BX],DX
- ADD DX,600
- ADD BX,2
- LOOP CLOOP
-
- ASSUME DS:INTERRUPTS ;The data segment will be the Interrupt area
- MOV AX,INTERRUPTS
- MOV DS,AX
-
- MOV AX,KEYBOARD_INT ;Get the old interrupt service routine
- MOV OLD_KEY_INT,AX ;address and put it into our location
- MOV AX,KEYBOARD_INT[2] ;OLD_KEYBOARD_INT so we can call it.
- MOV OLD_KEY_INT[2],AX
-
- MOV KEYBOARD_INT,OFFSET NEWPAD ;Now load the address of our notepad
- MOV KEYBOARD_INT[2],CS ;routine into the keyboard interrupt
-
-
- MOV AX,DOS_INT ;Get the old interrupt service routine
- MOV OLD_DOS_INT,AX ;address and put it into our location
- MOV AX,DOS_INT[2] ;OLD_DOS_INT so we can call it.
- MOV OLD_DOS_INT[2],AX
-
- MOV DOS_INT,OFFSET DOS_WATCH ;Now load the address of DOS_Watch
- MOV DOS_INT[2],CS ;routine into the interrupt vector.
-
- MOV AH,15 ;Ask for service 15 of INT 10H
- INT 10H ;This tells us how display is set up
- SUB AH,40 ;Move to twenty places before edge
- SHL AH,1 ;Mult by two (char & attribute bytes)
- MOV BYTE PTR FIRST_POSITION,AH ;Set screen cursor
- MOV STATUS_PORT,03BAH ;Assume this is a monochrome display
- TEST AL,4 ;Is it?
- JNZ EXIT ;Yes - jump out
- MOV SCREEN_SEG_OFFSET,8000H ;No - set up for graphics display
- MOV STATUS_PORT,03DAH
-
- EXIT: MOV DX,OFFSET LOAD_PAD ;Set up everything but LOAD_PAD to
- add dx,4200
- INT 27H ;stay and attach itself to DOS
- LOAD_PAD ENDP
-
- CODE_SEG ENDS
-
- END FIRST ;END "FIRST" so 8088 will go to FIRST first.
-
-