home *** CD-ROM | disk | FTP | other *** search
- ;======================================================================
- ; SLASHBAR is a memory resident interpreter for files prepared by the
- ; MAKEBAR utility. Bar-menu Description Files (.BDF) are first prepared
- ; to contain the keystrokes and prompts needed to perform the functions.
- ; The .BDF file is then or compiled to a BAR file. This
- ; file is loaded on the command line.
- ;
- ; Usage: SLASHBAR [path\]menuname [/n]
- ; where /n is the size buffer to allocate. /n is only valid for the
- ; first load and is specified in bytes. For obvious reasons it
- ; should be as large as the largest .BAR file you will use < 60K.
- ;----------------------------------------------------------------------
- LO_MEM SEGMENT AT 0000H
- ORG 41AH
- BIOS_HEAD DW ?
- BIOS_TAIL DW ?
- BIOS_BUF DW 16 DUP (?)
-
- LO_MEM ENDS
-
- ;======================================================================
- CSEG SEGMENT PARA PUBLIC 'CODE'
- ORG 100H ;COM file format
- STACK LABEL WORD ;Use PSP as stack when res.
-
- ASSUME CS:CSEG,DS:CSEG,ES:CSEG,SS:CSEG
-
- ;----------------------------------------------------------------------
- ; Equates - substituted literally when assembled.
- ;----------------------------------------------------------------------
- CR EQU 0DH ;HEX for carriage return
- LF EQU 0AH ; and line feed
- ;ALT-RIGHT SHIFT-TILDE
- HOTKEY EQU 35H ;SCAN code activating key
- SHIFT_MASK EQU 08H ;Mask to pick out 'shifts'
- ;1000 = ALT 0100 = CTRL
- ;0010 = L.SHIFT 0001 = R SHIFT
-
- NROW EQU 4 ;Number of rows in the window
- NCOL EQU 80 ;Number of cols in the window
- BOX_COL EQU 0 ;Left col of window on screen
- BOX_ROW EQU 0 ;Top of screen
- BW_ATTR EQU 7007H ;Monochrome window
- CO_ATTR EQU 0417H ;Color window
-
- SPACE EQU 20H ;Equivalents for some keys
- ESC_KEY EQU 1BH
- BS_KEY EQU 08H
- TAB_KEY EQU 09H
- RIGHT_ARROW EQU 4DH
- LEFT_ARROW EQU 4BH
- HOME_KEY EQU 47H
- END_KEY EQU 4FH
-
- MAX_CMD_VAL EQU 10 ;Use for error checking
-
- ;----------------------------------------------------------------------
- ; COM file entry point is at 100h
- ;----------------------------------------------------------------------
- ENTPT: JMP INITIALIZE ;Perform initialization
-
- COPYRIGHT DB "SlashBar 1.0 (c) 1987, Ziff-Davis Publishing Corp."
- DB CR,LF,"$",1AH
- DB "Robert L. Hummel"
-
- ;----------------------------------------------------------------------
- ; Data used by INT_9 procedure. Other data precedes other procedures.
- ;----------------------------------------------------------------------
- OLD_INT_9 DD 0 ;Storage for old vectors
- OLD_INT_16 DD 0
- OLD_INT_21 DD 0
- DOS_FLAG DD 0 ;Address of dos critical flag
-
- ACTIVE DB 0 ;Inside pop-up
- LO_FN_FLAG DB 0 ;When inside Int 21h
-
- DISPLAY_PAGE DB 0 ;Used by screen save
- CURSOR_POS DW 0 ; to restore info
-
- OLD_SS DW 0 ;To save stack
- OLD_SP DW 0 ; during switching
-
- ;======================================================================
- ; New Interrupt 9 routine. Invoked each key-press.
- ; Test to see if our key combination has been typed.
- ;----------------------------------------------------------------------
- INT_9 PROC FAR
- ASSUME CS:CSEG, DS:NOTHING, ES:NOTHING, SS:NOTHING
- ;(Flags saved by INT)
- STI ;Allow interrupts
- PUSH AX ;Save used register
-
- IN AL,60H ;Get key scan code
- CMP AL,HOTKEY ;Check if hot-key
- JNE PROCESS_KEY ;If not, continue on.
-
- MOV AH,2 ;Get shift status fn
- INT 16H ;Thru BIOS
-
- AND AL,0FH ;Test only for 'shift' keys
- CMP AL,SHIFT_MASK ;If they match our combination
- JE OUR_KEY ;then is our signal
- PROCESS_KEY:
- POP AX ;Restore register
- JMP DWORD PTR CS:OLD_INT_9 ;Process key as normal
- OUR_KEY:
- ;----------------------------------------------------------------------
- ; Reset the keyboard interrupt controller (forget the key stroke)
- ;----------------------------------------------------------------------
- IN AL,61H ;These instructions reset
- MOV AH,AL ; the keyboard.
- OR AL,80H
- OUT 61H,AL
- MOV AL,AH
- JMP SHORT $+2 ;I/O delay
- OUT 61H,AL
- CLI ;Disable interrupts and
- MOV AL,20H ;reset the int controller
- OUT 20H,AL
- STI ;Allow interrupts
-
- ;----------------------------------------------------------------------
- ; If program is already active, or DOS is busy, simply return.
- ;----------------------------------------------------------------------
- CMP CS:ACTIVE,0 ;If already active, can't call
- JNE RETURN_A
-
- MOV AX,CS:KEY_PTR ;If head of our key buffer
- CMP AX,CS:KEY_TAKE ; isn't = tail
- JNE RETURN_A ; we still have keys to lose
-
- INC CS:ACTIVE ;Turns off BIOS flag in INT_16
- MOV AH,1 ;If the BIOS key buffer
- INT 16H ; has keys in it
- MOV CS:ACTIVE,0
- JNZ RETURN_A ; don't pop up
-
- PUSH DS ;Save used registers
- PUSH BX
-
- LDS BX,CS:DOS_FLAG ;If DOS critical flag is not
- CMP BYTE PTR [BX],0 ; busy
- JE INVOKE ;We can pop up
-
- CMP CS:LO_FN_FLAG,0 ;If busy from low function
- JNE INVOKE ; go pop up
- RETURN_B:
- POP BX ;Restore other registers
- POP DS
- RETURN_A:
- POP AX ;Restore register
- IRET ;Go back where we came from
- INVOKE:
- ;----------------------------------------------------------------------
- ; From the video mode, determine the box colors to use.
- ;----------------------------------------------------------------------
- MOV WORD PTR CS:NCLR,CO_ATTR ;Use color window
- MOV AH,0FH ;Get current video mode fn
- CALL VIDEO ;Thru BIOS
- MOV CS:DISPLAY_PAGE,BH ;Save current page
- ;Valid video modes are:
- CMP AL,1 ;COLOR 40X25
- JZ MODE_OK
- CMP AL,3 ;COLOR 80x25
- JE MODE_OK
-
- MOV WORD PTR CS:NCLR,BW_ATTR ;Default to mono window
- CMP AL,7 ;MONO 80x25
- JE MODE_OK
- CMP AL,2
- JA RETURN_B ;Go back from whence we came
- MODE_OK:
- ;----------------------------------------------------------------------
- ; If here, routine becomes active, save all other used registers.
- ;----------------------------------------------------------------------
- MOV CS:ACTIVE,1 ;Set flag to prevent re-entry
-
- PUSH CX ;Save all registers for return
- PUSH DX
- PUSH DI
- PUSH SI
- PUSH ES
- PUSH BP
-
- MOV AX,CS ;Put our CS into these regs
- MOV DS,AX ;So we can find our data
- MOV ES,AX ;And our string moves
- ASSUME DS:CSEG,ES:CSEG ;Tell the Assembler
- MOV OLD_SS,SS ;Swap stacks after all
- MOV OLD_SP,SP ; registers are pushed
- CLI ;Turn off interrupts
- MOV SS,AX ;Put our stack in place
- MOV SP,OFFSET STACK
- STI ;Interrupts on
- ASSUME SS:CSEG ;Tell the Assembler
-
- ;----------------------------------------------------------------------
- ; Save the details of the current screen for later restoration.
- ;----------------------------------------------------------------------
- MOV AH,3 ;Get cursor position fn
- CALL VIDEO ;Thru BIOS
- MOV CURSOR_POS,DX ;Save position for
- ;restoration on exit
- ;----------------------------------------------------------------------
- ; Save section of screen we will be writing over.
- ;----------------------------------------------------------------------
- MOV DI,OFFSET SCREEN_BUF ;Destination for save
- MOV SI,0FFFFH ;Switch for proc to save
- CALL SCREEN
-
- ;----------------------------------------------------------------------
- ; Perform specific function.
- ;----------------------------------------------------------------------
- CALL CLR_BOX ;Draw box & border
- CALL MENU_TIME
- CANCEL:
- ;----------------------------------------------------------------------
- ; Restore the screen to original state.
- ;----------------------------------------------------------------------
- MOV SI,OFFSET SCREEN_BUF
- CALL SCREEN
-
- MOV AH,2 ;Set Cursor position fn
- MOV DX,CURSOR_POS ;Restore old cursor position
- CALL VIDEO ;Thru BIOS
-
- MOV AX,OLD_SS ;Restore previous stack
- MOV BX,OLD_SP
- CLI ;No interrupts
- MOV SS,AX
- MOV SP,BX
- STI ;Allow interrupts
-
- MOV ACTIVE,0 ;Turn off active flag
-
- POP BP ;Restore all used registers
- POP ES
- POP SI
- POP DI
- POP DX
- POP CX
- POP BX
- POP DS
- POP AX
-
- IRET ;Interrupt gets IRET
- INT_9 ENDP
-
- ;======================================================================
- ; BIOS Video Interrupt. Some older versions of the BIOS destroy the
- ; BP register inside the video routine.
- ;----------------------------------------------------------------------
- VIDEO PROC NEAR
-
- PUSH BP ;Preserve register
- INT 10H ;Call to BIOS
- POP BP ;Restore
- RET
-
- VIDEO ENDP
-
- ;======================================================================
- ; Perform the screen save/restore.
- ; SAVE: SI=FFFF, DI=buffer address
- ; RESTORE: SI=buffer address, DI=don't care
- ;----------------------------------------------------------------------
- SCREEN PROC NEAR
- ASSUME CS:CSEG, DS:CSEG, ES:CSEG, SS:NOTHING
-
- CLD ;String moves forward
- MOV BH,DISPLAY_PAGE ;Just to be sure, reset page
-
- MOV CX,NROW ;Row loop
- MOV ROW,BOX_ROW ;Init row pointer
- ROW_LOOP:
- PUSH CX ;Prepare for...
- MOV CX,NCOL ;...column loop
- MOV COL,BOX_COL ;Column Pointer
- COL_LOOP:
- CMP SI,0FFFFH ;SI =FFFF if SAVE
- JE DO_SAVE
- ;RESTORE
- LODSW ;AX <- [SI]
- ;AH=ATTR AL=CHAR
- CALL CRT_CHAR ;Write char to screen
- JMP SHORT DO_LOOP
- DO_SAVE:
- CALL SET_CUR ;Position cursor
- MOV AH,8 ;Get char & attribute fn
- CALL VIDEO ;Thru BIOS
- STOSW ;[di+=2]=ax
- DO_LOOP:
- INC COL ;Next column
- LOOP COL_LOOP ;Close Inner loop
-
- POP CX ;Return to outer loop
- INC ROW ;Next row
- LOOP ROW_LOOP ;Close Outer loop
- RET
-
- SCREEN ENDP
-
- ;======================================================================
- ; Clear a window (box) for our information on the screen.
- ; Add a border for a nice touch.
- ;----------------------------------------------------------------------
- BOX_MSG DB BOX_COL+2,BOX_ROW,0B5H,"SlashBar 1.0",0C6H,0
- BOX_CHARS DB 0C9H,0CDH,0BBH,0BAH,020H,0BAH,0C8H,0CDH,0BCH
-
- CLR_BOX PROC NEAR
-
- MOV AX,0600H ;Scroll entire window fn
- MOV CH,BOX_ROW ;Upper row
- MOV ROW,CH
- MOV CL,BOX_COL ;Left column
- MOV DH,BOX_ROW + NROW - 1 ;Lower row
- MOV DL,BOX_COL + NCOL - 1 ;Right column
- MOV BH,NCLR ;Window color
- CALL VIDEO ;Thru BIOS
-
- MOV BH,DISPLAY_PAGE ;This page
- MOV AH,NCLR ;This color
- MOV SI,OFFSET BOX_CHARS ;Source of characters
- MOV DX,CX ;Cursor from last call
- MOV CX,NROW ;Number of rows to draw
- CB_1:
- PUSH CX ;Save counter
- MOV COL,BOX_COL ;Set column
-
- LODSB ;Get leftmost char
- CALL CRT_CHAR ; write to screen
-
- LODSB ;Get middle char
- MOV CX,NCOL-2 ;Number copies to write
- CB_1A:
- INC COL ;Next column
- CALL CRT_CHAR ;Write char to screen
- LOOP CB_1A
- INC COL ;Last column
-
- LODSB ;Get rightmost char
- CALL CRT_CHAR ; put on screen
-
- INC ROW ;Next row
- POP CX ;Restore counter
- CMP CL,NROW ;If written last row
- JE CB_2 ; put new chars
- CMP CL,2 ;If 2nd row
- JE CB_2 ; get new chars
- SUB SI,3 ;back up & repeat
- CB_2:
- LOOP CB_1 ;Loop each line
-
- MOV SI,OFFSET BOX_MSG ;Put program name
- LODSW ; at this row,col
- MOV CURSOR_LOC,AX
- MOV AH,NCLR ; and this color
- CALL CRTZ ; on screen
- RET
-
- CLR_BOX ENDP
-
- ;======================================================================
- ; DOS Int 21h intercept. Set flag while uninterruptable
- ; The purpose of this procedure is to keep pop-up from taking control
- ; of the machine when doing so would cause a crash.
- ;----------------------------------------------------------------------
- INT_21 PROC FAR
-
- CMP AH,0 ;If program is using DOS fn 0
- JNE CHECK
- MOV AH,4CH ;Change it to 4Ch
- GO_DIRECT:
- MOV CS:LO_FN_FLAG,0 ;Not function 1-Ch
- JMP DWORD PTR CS:OLD_INT_21 ;Jump to original routine
- CHECK:
- CMP AH,0CH ;DOS functions call under 0DH
- JA GO_DIRECT
-
- MOV CS:LO_FN_FLAG,1 ; set this flag
-
- PUSHF ;Simulate INT
- CALL DWORD PTR CS:OLD_INT_21 ; return here
-
- MOV CS:LO_FN_FLAG,0 ;Turn off flag
- RET 2 ;Return to INT source and
- ;discard old flags
- INT_21 ENDP
-
- ;======================================================================
- ; Int 16 intercept. Use to feed keys to calling programs.
- ;----------------------------------------------------------------------
- LAST_CALL DB 0 ;Remember last call so first or
- ;last key can be removed
- INT_16 PROC FAR
- ASSUME CS:CSEG, DS:NOTHING, ES:NOTHING, SS:NOTHING
-
- CMP CS:ACTIVE,0 ;Don't steal our own 'strokes!
- JNE GOTO_BIOS ; get them thru BIOS
-
- CMP AH,2 ;Ignore calls for shift status
- JAE DONT_SAVE
- MOV CS:LAST_CALL,AH
- DONT_SAVE:
- STI ;Interrupts on
- PUSH BX ;Save used register
-
- MOV BX,CS:KEY_TAKE ;Pointer to next keystroke
- CMP BX,CS:KEY_PTR ;If no keys in our buffer
- JE POP_GOTO_BIOS ;Pass thru to BIOS
-
- CMP AH,2 ;Request for shift status
- JE POP_GOTO_BIOS ; goes thru BIOS always
-
- CMP AH,0 ;Wait for key
- JE UNLOAD_KEY
-
- CMP AL,1 ;Is key stroke ready?
- JNE POP_GOTO_BIOS ;return NZ if key ready
- OR AL,AL ;Generate a NZ
- POP BX
- RET 2 ;Discard old flags
- UNLOAD_KEY:
- MOV BX,CS:KEY_TAKE ;Get ptr to key in BX
- MOV AX,CS:[BX] ;Get the key in AX
- ADD CS:KEY_TAKE,2 ;Move the ptr along
-
- POP BX ;Restore register
- RET 2 ;Discard flags
-
- POP_GOTO_BIOS: POP BX
- GOTO_BIOS: JMP DWORD PTR CS:OLD_INT_16
-
- INT_16 ENDP
-
- ;=======================================================================
- ; INTERPRETER - Read the contents of menu file and perform functions.
- ; BP always contains the address of the start of the MENU buffer.
- ; NOTE: THIS PROGRAM MAKES USE OF THE FACT THAT A .COM FILE
- ; HAS CS=DS=ES=SS WHEN USING ADDRESSING WITH BP.
- ; THEREFORE, SET UP A STACK USING THE CS SEGMENT.
- ;----------------------------------------------------------------------
- ; Data structures.
- ;----------------------------------------------------------------------
- MENU_BASE DW FILE_DTA ;Real address of offset 0
- DTA_SIZE DW 4096 ;4k bytes by default
-
- OPT_PTR DW 0 ;Points to menu choice
- LEVEL DW 0 ;Depth of menu tree
- NOPT DW 0 ;Number options this menu
-
- KEY_PTR DW KEYS ;Points to next empty spot
- KEY_TAKE DW KEYS ;Points to available char
-
- CMD_TABLE DW ASK, CR_CMD, EXECUTE, INPUT, BAD_CMD, BAD_CMD
- DW BAD_CMD, TYPE_KEY, BAD_CMD, BAD_CMD, SEND
-
- CURSOR_LOC LABEL WORD
- COL DB 0 ;Display column
- ROW DB 0 ; row
-
- NCLR DB 07H ;Normal video color
- RCLR DB 70H ;Reverse video color
-
- ;=======================================================================
- ; Prime the pointers with their initial values.
- ;----------------------------------------------------------------------
- ASSUME CS:CSEG,DS:CSEG,ES:CSEG,SS:CSEG
- MENU_TIME PROC NEAR
-
- CLD ;String moves forward
- XOR DI,DI ;DI = 0
- MOV AX,OFFSET KEYS ;Initialize key buffer
- MOV KEY_PTR,AX
- MOV KEY_TAKE,AX
- MOV WORD PTR KEY_STK [DI],AX ;Starting KEY_PTR in stack
- MOV WORD PTR MENU_STK[DI],10 ;Offset into menu in stack
- MOV OPT_PTR,DI ;Point to option 0
- MOV LEVEL,DI ;We're at level 0
- MOV BP,MENU_BASE ;Always points to menu base
-
- ;----------------------------------------------------------------------
- ; Put the PROGRAM name on the screen.
- ;----------------------------------------------------------------------
- MOV ROW,BOX_ROW ;This row & column
- MOV COL,BOX_COL + NCOL - 12
-
- MOV AH,NCLR ;Normal color attribute
- MOV AL,0B5H ;Char to write
- CALL CRT_CHAR ;Write to screen
- MOV SI,BP ;Point to program name
-
- MOV CX,10 ;Maximum chars to write
- MT_1:
- INC COL ;Next column
- LODSB ;Get char at DS:SI
- OR AL,AL ;If 0
- JZ MT_2 ; end of string
- CALL CRT_CHAR ; else, write it
- LOOP MT_1 ; and continue
- MT_2:
- MOV AL,0C6H ;Close box
- CALL CRT_CHAR ;Write char
-
- ;----------------------------------------------------------------------
- ; Menus are built from scratch.
- ;----------------------------------------------------------------------
- BUILD_MENU:
- CALL CLR_LINES ;Clear inside of window
-
- MOV DI,LEVEL ;The menu level
- SHL DI,1 ; *2 for word access
- MOV AX, WORD PTR KEY_STK[DI] ;Point to next key save point
- MOV KEY_PTR,AX ; and put where it's used
-
- CALL GET_MENU_HEAD ;Offset of menu in DI
- MOV AX,[BP][DI] ;Offset 0 has number opts
- MOV NOPT,AX
-
- CALL WRITE_NAMES ;Write the option names
- CALL WRITE_HELP ;Write the help lines
- CALL GET_KEY ;From user
-
- OR AL,AL ;AL = 0 If extended ascii
- JNZ ASCII_KEY
-
- CALL MOVE_BAR ;Could be left/right arrow
- JMP BUILD_MENU ; or home/end
-
- ;----------------------------------------------------------------------
- ; ASCII key could be option letter, CR, ESC, or mistake.
- ;----------------------------------------------------------------------
- ASCII_KEY:
- CALL MAKE_UC ;Make AL upper case
- CALL MATCH_KEY ;Return NC if match and
- ; AL contains option #
- JNC MATCH_FOUND ;No match found
- CALL BEEP
- JMP BUILD_MENU
- MATCH_FOUND:
- CMP AL,0FFH ;AL=FF if ESC
- JNE READ_SCRIPT ;Else, perform functions
-
- ;----------------------------------------------------------------------
- ; The ESC key was hit. Back up one menu. If at top menu, exit.
- ; backing up removes any keystrokes put in by the current menu.
- ;----------------------------------------------------------------------
- CMP LEVEL,0 ;If at top menu
- JE CANCEL_MENU ; leave
- DEC LEVEL ;Back up
- MOV OPT_PTR,0
- JMP BUILD_MENU ;Reconstruct display
- CANCEL_MENU:
- MOV KEY_PTR,OFFSET KEYS ;Flush the buffer
- RET ;Return & Exit
-
- ;----------------------------------------------------------------------
- ; Interpret the option script.
- ;----------------------------------------------------------------------
- READ_SCRIPT:
- CALL GET_MENU_HEAD ;Set DI = menu offset
- MOV AX,OPT_PTR ;Each option takes 6 bytes
- INC AX ;Extra 6 to point to token ptr
- MOV BL,6 ;3 words = 6 bytes
- MUL BL ;Gives Additional offset in AX
- ADD DI,AX ;DI is offset from menu head
- MOV SI,[BP][DI] ;SI is offset to token
- ADD SI,BP ;Real address
- GET_TOKEN:
- LODSB ;Get command token
- MOV BL,AL ;Put in base register
- CMP BL,MAX_CMD_VAL
- JA BAD_CMD
- SHL BL,1 ;*2 for word access
- XOR BH,BH ;Top is 0
- JMP CMD_TABLE[BX] ;Execute based on value
- BAD_CMD:
- ;If here, the .BAR file is bad, no recovery
- ;Use the save exit as a top-level-escape
- JMP CANCEL_MENU
-
- ;----------------------------------------------------------------------
- ; ASK: Type the following string in the window
- ; 1st line is used for queries.
- ;----------------------------------------------------------------------
- ASK:
- CALL CLR_LINES ;Clear inside of window
- MOV ROW,BOX_ROW + 1 ;Position the cursor
- MOV COL,BOX_COL + 2
- MOV AH,NCLR ;Attribute to use
- CALL CRTZ ;Copy chars till 0
- JMP GET_TOKEN ;Get next instruction
-
- ;----------------------------------------------------------------------
- ; CR: Put a CR in the buffer.
- ;----------------------------------------------------------------------
- CR_CMD:
- MOV AX,1C0DH ;Put a carriage return
- CALL SAVE_KEY ; in our key buffer
- JMP GET_TOKEN ;Get next instruction
-
- ;----------------------------------------------------------------------
- ; EXECUTE: transfer control to a lower menu.
- ;----------------------------------------------------------------------
- EXECUTE:
- INC LEVEL ;Next menu level
- MOV DI,LEVEL ;Convert to index
- CMP DI,32 ;Maximum level of menus
- JB LEVEL_OK
- MENU_ERROR:
- CALL BEEP ;Sound off!
- JMP CANCEL_MENU ;And leave no trace
- LEVEL_OK:
- SHL DI,1 ;Index into tables
- MOV AX,KEY_PTR ;Save current key_ptr
- MOV WORD PTR KEY_STK[DI],AX ; to restore
- ;Following token is
- LODSW ; offset of new menu
- MOV WORD PTR MENU_STK[DI],AX ;Saved in "stack"
- MOV OPT_PTR,0
- JMP BUILD_MENU ;Make new picture
-
- ;----------------------------------------------------------------------
- ; INPUT: Accept keystrokes from the user until CR.
- ; 2nd line is used for responses.
- ;----------------------------------------------------------------------
- INPUT:
- CALL BUFFERED_INPUT ;Buffered input from console
- JNC GET_TOKEN ;NC if all went ok
- JMP BUILD_MENU ;Else rebuild menu
-
- ;----------------------------------------------------------------------
- ; TYPE: Put the following keystrokes into the key buffer.
- ;----------------------------------------------------------------------
- TYPE_KEY:
- XOR AH,AH ;High byte is 0
- LODSB ;Get char in AL
- OR AL,AL ;0 If end of sequence
- JE GET_TOKEN ;Look for next command
- CMP AL,0FEH ;Extended ascii switch
- JNE TYPE_1 ;Put char out as is
- LODSB ;Get extended code
- CMP AL,0FEH
- JNE TYPE_A
- MOV AX,1C0AH ;Double FE FE = ctrl-enter
- JMP SHORT TYPE_2
- TYPE_A:
- XCHG AH,AL ;Put code in high byte
- JMP SHORT TYPE_2 ;Stuff in buffer
- TYPE_1:
- MOV AH,1CH ;Add the high bytes to
- CMP AL,CR ; these selected keys
- JE TYPE_2 ; for compatibility
-
- MOV AH,1
- CMP AL,ESC_KEY
- JE TYPE_2
-
- MOV AH,0EH
- CMP AL,BS_KEY
- JE TYPE_2
- CMP AL,7FH
- JE TYPE_2
-
- INC AH
- CMP AL,TAB_KEY
- JE TYPE_2
- XOR AH,AH
- TYPE_2:
- CALL SAVE_KEY ;Put in KEYS buffer
- JMP TYPE_KEY ;Try again
-
- ;----------------------------------------------------------------------
- ; SEND: Signal the end of the pop-up task.
- ;----------------------------------------------------------------------
- SEND:
- MOV BX,KEY_PTR ;Pointer to next keystroke
- CMP BX,KEY_TAKE ;If no keys in our buffer
- JE MENU_EXIT ;No action needed
-
- CMP LAST_CALL,0 ;If last call was wait-for-key
- JE USE_FIRST_KEY ; stuff first key in buffer
-
- SUB KEY_PTR,2 ;Point to last valid key
- SUB BX,2 ; move the pointer
- JMP SHORT REMOVE_KEY ;Put in BIOS buffer
- USE_FIRST_KEY:
- MOV BX,KEY_TAKE ;Remove first key
- ADD KEY_TAKE,2 ; advance pointer
- REMOVE_KEY:
- MOV CX,WORD PTR [BX] ;Take out the LAST key
-
- PUSH DS ;Set up for low memory access
- XOR AX,AX
- MOV DS,AX
- ASSUME DS:LO_MEM
- MOV BX,OFFSET BIOS_HEAD ;Start of bios key buffer
-
- CLI
- MOV WORD PTR [BX][0],001EH ;Set the head
- MOV WORD PTR [BX][2],0020H ;Set the Tail
- MOV WORD PTR [BX][4],CX ;Put key in buffer
- STI ;Allow interrupts
-
- POP DS ;Restore the register
- ASSUME DS:CSEG ;Tell the assembler
- MENU_EXIT:
- RET
-
- MENU_TIME ENDP
-
- ;======================================================================
- ; Put offset of current menu_head into DI. MENU_STK[LEVEL*2]
- ; DI changed. Other registers preserved.
- ;----------------------------------------------------------------------
- GET_MENU_HEAD PROC NEAR
-
- MOV DI,LEVEL
- SHL DI,1
- MOV DI,WORD PTR MENU_STK[DI]
- RET
-
- GET_MENU_HEAD ENDP
-
- ;======================================================================
- ; Write the current menu option choices to the screen.
- ; AX,CX,DX,SI,DI changed. Others preserved.
- ;----------------------------------------------------------------------
- WRITE_NAMES PROC NEAR
-
- MOV ROW,BOX_ROW + 1 ;Position is one row down
- MOV COL,BOX_COL + 1 ;1 col over
-
- XOR DX,DX ;Option counter
- MOV CX,NOPT ;Number of options this menu
- CALL GET_MENU_HEAD ;In DI
- WN_1:
- MOV SI,[BP][DI][2] ;SI is offset to name
- ADD SI,BP ;SI points to name
- WN_2:
- MOV AH,NCLR ;Normal color
- MOV AL,SPACE ; with a space
- INC COL ;Separate the names
- CALL CRT_CHAR
- CMP OPT_PTR,DX ;Is this the current option
- JNE WN_3
- MOV AH,RCLR ;Yes, use reverse color
- WN_3:
- CALL CRTZ ;Copy until 0 to CRT
- INC DX ;1 string complete
- ADD DI,6 ;Point to next ptr to name
- LOOP WN_1 ;Repeat for number of options
- RET
-
- WRITE_NAMES ENDP
-
- ;======================================================================
- ; Write the help line for the current option below the names.
- ; AX,BX,SI,DI changed. Others preserved.
- ;----------------------------------------------------------------------
- WRITE_HELP PROC NEAR
-
- MOV ROW,BOX_ROW + 2
- MOV COL,BOX_COL + 2
-
- CALL GET_MENU_HEAD
- MOV AX,OPT_PTR ;3 WORD offset for each opt
- MOV BL,6
- MUL BL ;Gives Additional offset in AX
- ADD DI,AX ;DI is ptr to offset of help
- MOV SI,[BP][DI][4] ;SI is offset ptr to help
- ADD SI,BP
- MOV AH,NCLR ;Normal color
- CALL CRTZ ;Write string to CON
- RET
-
- WRITE_HELP ENDP
-
- ;======================================================================
- ; Read a key from the console with no echo.
- ; Return in AX. Other registers preserved.
- ;----------------------------------------------------------------------
- GET_KEY PROC NEAR
-
- XOR AH,AH ;AH=0, wait for key
- INT 16H ; Thru BIOS
- RET
-
- GET_KEY ENDP
-
- ;======================================================================
- ; Keystroke was extended ascii. If left/right arrow, move opt_ptr.
- ; BX,CX changed. Other registers preserved.
- ;----------------------------------------------------------------------
- MOVE_BAR PROC NEAR
-
- MOV BX,OPT_PTR ;Current position
- MOV CX,NOPT ;Maximum position is # opt
- DEC CX ; minus one
-
- CMP AH,RIGHT_ARROW ;Move right
- JNE MB_1
- INC BX ;Increase pointer
- CMP BX,CX ;Past max?
- JBE MB_EXIT ;No, exit
- MB_0:
- XOR BX,BX ;Yes, reset to 0
- JMP SHORT MB_EXIT ;and leave
- MB_1:
- CMP AH,LEFT_ARROW ;Move left
- JNE MB_2
- DEC BX ;Decrease pointer
- JNS MB_EXIT ;Did it go negative?
- MB_1A:
- MOV BX,CX ; yes, wrap to max
- MB_EXIT:
- MOV OPT_PTR,BX ;Change pointer
- RET ;Leave
- MB_2:
- CMP AH,HOME_KEY ;Home - go to 0
- JE MB_0
- MB_3:
- CMP AH,END_KEY ;End - move to max
- JE MB_1A
- CALL BEEP
- RET
-
- MOVE_BAR ENDP
-
- ;======================================================================
- ; Make the character in AL UPPER case.
- ;----------------------------------------------------------------------
- MAKE_UC PROC NEAR
-
- CMP AL,'a'
- JB UC_1
- CMP AL,'z'
- JA UC_1
- SUB AL,20H
- UC_1:
- RET
- MAKE_UC ENDP
-
- ;======================================================================
- ; Search current names for matching first letter. Return CY if no match.
- ; If CR, choose current option, and return in AL. If ESC, set AL=FF.
- ; AX,BX,DX changed. Others preserved.
- ;----------------------------------------------------------------------
- MATCH_KEY PROC NEAR
-
- CMP AL,ESC_KEY ;If ESC key hit
- JNE MK_0
- MOV AL,0FFH ;Signal code
- MK_CLC:
- CLC
- MK_EXIT:
- RET ;Return
- MK_0:
- MOV BX,AX ;Save key
- MOV AX,OPT_PTR ;Current option in AL
- CMP BL,CR ;If CR struck
- JE MK_CLC ;Return option number
-
- XOR DX,DX ;Option counter
- MOV CX,NOPT ;Number of options this menu
- CALL GET_MENU_HEAD ;In DI
- MK_1:
- MOV SI,[BP][DI][2] ;SI is offset to name
- ADD SI,BP ;SI points to opt name
- LODSB ;Get first letter in AL
- CMP AL,BL ;Does key match?
- JE MK_2
- INC DX ;Next option count
- ADD DI,6 ;Point to next ptr to name
- LOOP MK_1 ;Repeat for number of options
- STC ;Match not found
- RET
- MK_2:
- MOV AX,DX ;Put option match in AL
- MOV OPT_PTR,AX ;And in pointer
- JMP MK_CLC
-
- MATCH_KEY ENDP
-
- ;======================================================================
- ; Copy an ASCIIZ string to the console at the current cursor location.
- ; Cursor position is updated. SI points to string and is moved. AH
- ; contains the attribute to used for the string.
- ; AX,SI changed. Other registers preserved.
- ;----------------------------------------------------------------------
- CRTZ PROC NEAR
- CRTZ_1:
- LODSB ;Get character
- OR AL,AL ;If char is 0
- JE CRTZ_2 ; end of string
- CALL CRT_CHAR
- INC COL
- JMP CRTZ_1
- CRTZ_2:
- RET
-
- CRTZ ENDP
-
- ;======================================================================
- ; Output the char in AL at the stored cursor position.
- ; AH contains the attribute to be used.
- ; Preserve all registers.
- ;----------------------------------------------------------------------
- CRT_CHAR PROC NEAR
-
- PUSH AX ;Save used registers
- PUSH BX
- PUSH CX
-
- CALL SET_CUR ;Set the cursor
- MOV CX,1 ;Write 1 char
- MOV BL,AH ;Use this attribute
- MOV AH,9 ;Write char & attr
- MOV BH,DISPLAY_PAGE ;This page
- CALL VIDEO ; Thru BIOS
-
- POP CX ;Restore registers
- POP BX
- POP AX
- RET
-
- CRT_CHAR ENDP
-
- ;======================================================================
- ; Clear the line in AL. AX,BX,CX,DX destroyed.
- ;----------------------------------------------------------------------
- CLR_LINES PROC NEAR
-
- MOV AX,0600H ;Scroll screen Function
- MOV CH,BOX_ROW + 1 ;Upper row
- MOV DH,BOX_ROW + NROW - 2 ;Lower row
- MOV CL,BOX_COL + 1 ;Left col
- MOV DL,BOX_COL + NCOL - 2 ;Right col
- MOV BH,NCLR ;Attribute
- CALL VIDEO ;BIOS video
- RET
-
- CLR_LINES ENDP
-
- ;======================================================================
- ; Position the cursor at ROW,COL.
- ; Preserve all registers.
- ;----------------------------------------------------------------------
- SET_CUR PROC NEAR
-
- PUSH AX ;Save used registers
- PUSH BX
- PUSH DX
-
- MOV DX,CURSOR_LOC ;Load both row & col
- MOV AH,2 ;Move cursor fn
- MOV BH,DISPLAY_PAGE ;Current page
- CALL VIDEO ; Thru BIOS
-
- POP DX ;Restore registers
- POP BX
- POP AX
- RET
-
- SET_CUR ENDP
-
- ;======================================================================
- ; Save the key in AX in KEYS buffer
- ;----------------------------------------------------------------------
- SAVE_KEY PROC NEAR
-
- PUSH BX ;Save used registers
- PUSH CX
-
- MOV CX,KEY_PTR ;Current pointer
- MOV BX,CX ; also in BX
- SUB CX,OFFSET KEYS ;Get # bytes
- CMP CX,512 ;More than allowed?
- JE SK_1 ;Simply ignore
- MOV [BX],AX ;Store key
- ADD KEY_PTR,2 ;Move pointer
- SK_1:
- POP CX ;Restore registers
- POP BX
- RET
-
- SAVE_KEY ENDP
-
- ;======================================================================
- ; Read keys from the keyboard until a <CR>
- ;----------------------------------------------------------------------
- BUFFERED_INPUT PROC NEAR
-
- PUSH AX ;Save registers
- PUSH CX
- PUSH SI
- BUF_ERASE:
- MOV ROW,BOX_ROW + 2 ;Position cursor
- MOV COL,BOX_COL + 1
- CALL SET_CUR
- MOV AX,0A20H ;Fill with blanks
- MOV BH,DISPLAY_PAGE
- MOV CX,NCOL - 2
- CALL VIDEO ; Thru BIOS
-
- MOV SI,OFFSET INKEY_BUF ;Point to start of buffer
- BUF_1:
- MOV CX,SI ;Calculate buffer length
- SUB CX,OFFSET INKEY_BUF ; in CX
- CALL SET_CUR ;Position cursor
- CALL GET_KEY ;Read a key from the kbd
-
- OR AL,AL ;If low byte is 0
- JZ BUF_1 ; not ascii
-
- CMP AL,CR ;Enter key
- JE BUF_CR
-
- CMP AL,ESC_KEY ;Escape
- JE BUF_ESC
-
- CMP AL,BS_KEY ;Backspace
- JE BUF_BS
-
- CMP CX,76 * 2 ;Maximum bytes allowed
- JA BUF_2A
- BUF_1A:
- MOV [SI],AX ;Save key in INKEY_BUF
- ADD SI,2 ;Point to next entry
- BUF_2:
- MOV AH,NCLR
- CALL CRT_CHAR ;Write AL at row,col
- INC COL ;Next column
- JMP BUF_1 ;Get more keys
- BUF_BS:
- OR CX,CX ;Any keys in buf?
- JNZ BUF_3
- BUF_2A:
- CALL BEEP
- JMP BUF_1
- BUF_3:
- SUB SI,2 ;Remove key
- DEC COL ;Write over char
- MOV AL,SPACE ; with space
- MOV AH,NCLR ;Normal color
- CALL CRT_CHAR ;Do it
- JMP BUF_1
- BUF_ESC:
- OR CX,CX ;If chars in buf
- JNZ BUF_ERASE ;Erase them all
- STC ;Carry means we're backing out
- JMP SHORT BUF_RET
- BUF_CR:
- OR CX,CX ;If no chars
- JZ BUF_OK ; simply return
- SHR CX,1 ;Number of words to transfer
- MOV SI,OFFSET INKEY_BUF
- CLD
- BUF_LOOP:
- LODSW
- CALL SAVE_KEY
- LOOP BUF_LOOP
- BUF_OK:
- CLC
- BUF_RET:
- POP SI ;Restore regs
- POP CX
- POP AX
- RET
-
- BUFFERED_INPUT ENDP
-
- ;======================================================================
- ; Beep at the terminal.
- ;----------------------------------------------------------------------
- BEEP PROC NEAR
-
- PUSH AX ;Save register
- MOV AX,0E07H ;write a 'beel'
- CALL VIDEO ; Thru BIOS
- POP AX ;Restore
- RET
-
- BEEP ENDP
-
- ;======================================================================
- ; Hook the necessary interrupts to avoid a collision. Read command line
- ; Parameters. Terminate and Stay Resident (TSR).
- ;----------------------------------------------------------------------
- GREEDY_MSG DB "/n Too Big$"
- BIG_FILE DB "File Too Big$"
- BAD_FILE_MSG DB "Error Opening File$"
- USAGE_MSG DB "Usage: SLASHBAR [path]menuname.ext [/n]$"
-
- INITIALIZE PROC NEAR
- ASSUME CS:CSEG, DS:CSEG, ES:CSEG, SS:CSEG
-
- MOV DX,OFFSET COPYRIGHT ;Say who we are
- MOV AH,9 ;Display string function
- INT 21H ;Thru DOS
-
- CALL CHECK_VERSION ;Version 2.0+ or don't return
-
- ;----------------------------------------------------------------------
- ; Check if already loaded in memory. Don't load multiple copies.
- ; When this routine ends, ES points to usable copy in memory. It may
- ; not be the same as CS.
- ;----------------------------------------------------------------------
- MOV WORD PTR [ENTPT+0],0 ;Modify to avoid false match
- MOV WORD PTR [ENTPT+2],0
-
- XOR BX,BX ;BX = segment to compare
- MOV AX,CS ;AX = our segment
- NEXT_PARA:
- INC BX ;Next paragraph
- MOV ES,BX ;Set search segment
- CMP AX,BX ;If current paragraph...
- JE END_SEARCH ;...stop
- MOV SI,OFFSET ENTPT ;String to compare
- MOV DI,SI ;Offset is same
- MOV CX,16 ;Compare first 16 words
- REP CMPSW ;CMP DS:SI TO ES:DI
- OR CX,CX ;All matched?
- JNZ NEXT_PARA ;No, continue search
- JMP SHORT SIZE_OK ;Found a copy at ES
-
- ;----------------------------------------------------------------------
- ; Didn't find a copy in memory. Look for memory size switch.
- ;----------------------------------------------------------------------
- END_SEARCH:
- MOV DI,80H ;# chars on command line
- MOV CL,[DI] ; in CL
- XOR CH,CH ;CH = 0
- INC DI ;Point to 1st char
- MOV AL,'/' ;Look for slash
- REPNE SCASB ;Do it for CX chars
- JCXZ SIZE_OK ;No switch on line
-
- MOV SI,DI ;Point SI to n parameter
- DEC DI ;Make sure any file name
- MOV BYTE PTR [DI],CR ; has return after it
- MOV DI,10 ;Base 10 (decimal)
- MOV CX,5 ;Maximum 5 digits
- XOR BX,BX ;Size in BX
- GET_MEM_SIZE:
- LODSB ;Get digit
- SUB AL,30H ;ASCII to digit
- CMP AL,9 ;Must be 0-9
- JA SAVE_SIZE ; else, end of num
- XCHG AX,BX ;Put digit in BX
- MUL DI ;Multiply sum x 10
- XOR BH,BH ;Make BX single digit
- ADD BX,AX ;Sum in BX
- LOOP GET_MEM_SIZE ;Continue
- SAVE_SIZE:
- MOV DTA_SIZE,BX ;Place in variable
- XOR AX,AX ;Check 64 K limit
- DEC AX
- SUB AX,BX
- CMP AX,OFFSET LAST_BYTE
- JA SIZE_OK
- MOV DX,OFFSET GREEDY_MSG
- ERROR_EXIT:
- MOV AH,9 ;Display string fn
- INT 21H ; Thru DOS
- MOV AX,4C01H ;Terminate with error=1
- INT 21H ; Thru DOS
- SIZE_OK:
- ;----------------------------------------------------------------------
- ; Read the command line for a path/file spec.
- ; ES may point to the resident copy!
- ;----------------------------------------------------------------------
- MOV SI,81H ;Command line in PSP
- FIND_START:
- LODSB ;Get char
- CMP AL,SPACE ;If a space
- JE FIND_START ; skip to next char
- CMP AL,CR ;If NOT CR
- JNE HAVE_START ; found start of spec
- MOV DX,OFFSET USAGE_MSG ;CR = error, no file name
- JMP ERROR_EXIT
- HAVE_START:
- MOV DX,SI
- DEC DX ;Name starts here
- FIND_END:
- LODSB ;Get char
- CMP AL,SPACE ;A space
- JE NAME_OK
- CMP AL,CR ;or CR ends name
- JNE FIND_END
- NAME_OK:
- DEC SI ;Back up 1 char
- MOV BYTE PTR [SI],0 ; make ASCIIZ
- MOV AX,3D00H ;Open for reading
- INT 21H ; Thru DOS
- JNC OPEN_OK
- FILE_ERR:
- MOV DX,OFFSET BAD_FILE_MSG
- JMP ERROR_EXIT
- OPEN_OK:
- MOV BX,AX ;Save handle in BX
- MOV AX,4202H ;Move file pointer
- XOR CX,CX ; 0 bytes from end
- XOR DX,DX
- INT 21H ; Thru DOS
- JC FILE_ERR
-
- CMP AX,DTA_SIZE ;AX has # bytes in file
- JBE FILE_FINE ;Size OK
- MOV DX,OFFSET BIG_FILE
- JMP ERROR_EXIT
- FILE_FINE:
- PUSH AX ;Number of bytes to read
- MOV AX,4200H ;Move file pointer
- XOR CX,CX ; 0 bytes from start
- XOR DX,DX
- INT 21H ; Thru DOS
- POP CX
- JC FILE_ERR
-
- MOV AH,3FH ;Read file fn
- MOV DX,OFFSET FILE_DTA ;Put data at this offset
- PUSH DS ;(Save DS)
- PUSH ES ;Put ES (resident segment)
- POP DS ; into DS (DS:DX is DTA)
- INT 21H ;Thru DOS
- POP DS ;Restore old DS
- JC FILE_ERR
-
- MOV AH,3EH ;Close file Fn
- INT 21H ; Thru DOS
-
- MOV CX,CS ;Check if ES=CS, i.e.,
- MOV BX,ES ;there is no resident copy
- CMP CX,BX
- JE KEEP
-
- MOV AX,4C00H
- INT 21H
- KEEP:
- ;----------------------------------------------------------------------
- ; Get a pointer to the DOS Critical Flag, a one-byte location in low memory
- ; that is set when DOS is in an uninterruptable state. Location is returned
- ; in ES:BX. This is undocumented, but works in DOS 2.0 - 3.21
- ;----------------------------------------------------------------------
- PUSH ES
- MOV AH,34H ;Get Interrupt Flag address
- INT 21H
-
- MOV WORD PTR DOS_FLAG[0],BX ;offset
- MOV WORD PTR DOS_FLAG[2],ES ;segment
- POP ES
-
- ;----------------------------------------------------------------------
- ; Hook the keyboard interrupt 9h for the hot-key detection routine.
- ; Hook Int 16h for BIOS keyboard control.
- ; Hook DOS Interrupt 21h,25h,26h and BIOS 13h to set busy flags.
- ;----------------------------------------------------------------------
- MOV AL,9 ;Interrupt number
- MOV DI,OFFSET OLD_INT_9 ;Store vector here
- MOV DX,OFFSET INT_9 ;New interrupt procedure
- CALL SET_INT ;Make change
-
- MOV AL,16H
- MOV DI,OFFSET OLD_INT_16
- MOV DX,OFFSET INT_16
- CALL SET_INT
-
- MOV AL,21H
- MOV DI,OFFSET OLD_INT_21
- MOV DX,OFFSET INT_21
- CALL SET_INT
-
- ;----------------------------------------------------------------------
- ; Deallocate the copy of the environment loaded with the program.
- ; Establish memory residency and terminate.
- ;----------------------------------------------------------------------
- MOV AX,WORD PTR DS:[2CH] ;Address of environment
- MOV ES,AX ;In ES register
- MOV AH,49H ;Release allocated memory
- INT 21H ;Thru DOS
-
- MOV DX,OFFSET LAST_BYTE - OFFSET CSEG + 15
- ADD DX,DTA_SIZE ;Total size in bytes
- MOV CL,4 ; /16 =
- SHR DX,CL ;In paras
- MOV AX,3100H ;Keep (TSR)
- INT 21H ;Thru DOS
-
- INITIALIZE ENDP
-
- ;======================================================================
- ; Check for the correct version of DOS. Return if 2.0 or later.
- ; Terminate if 1.x. AX destroyed on return.
- ;----------------------------------------------------------------------
- BAD_DOS_MSG DB "SlashBar: Requires DOS 2.0+",CR,LF,"$"
-
- CHECK_VERSION PROC NEAR
- ASSUME CS:CSEG, DS:CSEG, ES:CSEG, SS:CSEG
-
- MOV AH,30H ;Get DOS version number fn
- INT 21H ;Thru DOS
- ;AL=major ver #,AH=minor ver #
- CMP AL,02 ;Compare to 2.0
- JAE VER_OK ;If 2.0 or later, go on.
-
- MOV DX,OFFSET BAD_DOS_MSG ;DS:DX is message
- MOV AH,9 ;Display string fn
- INT 21H ;Thru DOS
- INT 20H ;Exit 1.0 style
- VER_OK:
- RET
-
- CHECK_VERSION ENDP
-
- ;======================================================================
- ; Get/Save/Set the interrupt vector. AL contains vector number.
- ; ES:DI points to DWORD destination for old address.
- ; DS:DX points to new interrupt address. AX destroyed.
- ;----------------------------------------------------------------------
- SET_INT PROC NEAR
- ASSUME CS:CSEG, DS:CSEG, ES:CSEG, SS:CSEG
-
- PUSH ES
- PUSH AX ;Save vector # in AL
- MOV AH,35H ;Get address function
- INT 21H ;Thru DOS
- MOV WORD PTR [DI+0],BX ;Save address in ES:DI
- MOV WORD PTR [DI+2],ES
- POP AX ;Get AL back
- MOV AH,25H ;Set new address to DS:DX
- INT 21H ;Thru DOS
- POP ES
- RET
-
- SET_INT ENDP
-
- ;======================================================================
- ; Data here is allocated after the program loads into memory to save space
- ; in the COM file so the basic listing will be smaller.
- ; PC variable used to keep track of relative addresses.
- ;----------------------------------------------------------------------
- PC = $ ;Set imaginary counter
-
- SCREEN_BUF = PC ;DB NROW*NCOL*2 DUP(?)
- PC = PC + NROW * NCOL * 2
-
- KEYS = PC ;DW 256 DUP(0)
- PC = PC + 256 * 2
- ;For buffered input
- INKEY_BUF = PC ;DW 76 DUP(0)
- PC = PC + 76 * 2
-
- KEY_STK = PC ;DW 32 DUP(0)
- PC = PC + 32 * 2
-
- MENU_STK = PC ;DW 32 DUP(0)
- PC = PC + 32 * 2
-
- FILE_DTA = PC
- LAST_BYTE = PC
-
- CSEG ENDS
- END ENTPT