home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Power-Programmierung
/
CD1.mdf
/
assemblr
/
library
/
sampler0
/
pcmap.asm
< prev
next >
Wrap
Assembly Source File
|
1989-04-22
|
39KB
|
1,105 lines
page 58,132
;----------------------------------------------------------------
; PCMAP 2.0 - Jeff Hasty (CompuServe 71121,2352) - April, 1989
; Documentation in PCMAP2.DOC
;----------------------------------------------------------------
;----------------------------------------------------------------
; EQUATES
;----------------------------------------------------------------
MAX_BLK EQU 23 ;Number of spaces in table
INT9_BUSY EQU 1 ;Mask for BUSY byte
INT10_BUSY EQU 2 ;Mask for BUSY byte
SHIFT_MASK EQU 8 ;Mask for hot key (8=Alt)
HOTKEY EQU 19H ;Scan code (19h=P)
CR EQU 0DH ; ASCII carriage return
LF EQU 0AH ; ASCII line feed
TAB EQU 09h ; ASCII tab
BLANK EQU 20h ; ASCII space character
;----------------------------------------------------------------
; START - entry point for command-line mode
;----------------------------------------------------------------
_TEXT SEGMENT PARA PUBLIC 'CODE' ;set up for .COM file
ASSUME CS:_TEXT,DS:_TEXT
ORG 100H
START:
JMP RES ;jump to installation routines
;----------------------------------------------------------------
; RESIDENT DATA AREA
;----------------------------------------------------------------
ID DB "PCMAP 2.0 - Jeff Hasty (CompuServe 71121,2352)"
DB " - April, 1989",1Ah
HEADING_MSG DB CR,LF
DB "Segment Size Program"
DB CR,LF
DB "Address Owner (para) Type Name"
DB CR,LF
DB "0000",18 DUP(' '),0
BLOCK1_MSG DB 10 DUP (' '),"DOS + Drivers",CR,LF,0
CR_LF_MSG DB CR,LF,0
COM_MSG DB "COMMAND.COM"
PSP_MSG DB "PSP"
ENV_MSG DB "ENV"
UNK_MSG DB "(Unknown)"
FREE_MSG DB "(Free)"
SPACE3_MSG DB " "
SPACE_MSG DB 7 DUP(' '),0
TABLE_FULL_MSG DB "Out of space ",0
PROGRAM_ID DB "PCMAP 2.0",0
HIT_ANY_KEY DB " - Hit any key to return...",0
DISABLE DB 0 ;flag to disable if cannot uninstall
TSR_MODE DB 1 ;=0 if command line mode
VER3 DB 0 ;=1 if Version >= 3.0
LAST_BLOCK DB 0 ;=1 if last MCB
TABLE_FULL DB 0 ;=1 if table full
CURSOR_POS DW 0 ;to store cursor position
BIOS_SEG DW 40H ;address of bios data area
DIFF DW 0 ;# of chars on a line > 80
N_BLK DB 0 ;Count table entries
OUR_SS DW 0 ; used for stack swap
OUR_SP DW 0
THEIR_SS DW 0
THEIR_SP DW 0
RETADDR DW 0
ADDR_INT9H DD 0 ;to save original vectors
ADDR_INT10H DD 0
BUSY DB 0 ;to store status of int 9 and int 10h
;----------------------------------------------------------------------
; INT9H - entry point for memory-resident mode.
; pressing any key causes entry here.
;----------------------------------------------------------------------
INT9H PROC FAR
STI ;interrupts on
PUSH AX ;save working register
CMP CS:DISABLE,-1 ;if disabled, do nothing
JE NOT_US
IN AL,60H ;get key from keyboard port
CMP AL,HOTKEY ;is it our hotkey?
JNE NOT_US ;if not, exit
MOV AH,2 ;otherwise
INT 16H ;get shift status
AND AL,0FH
CMP AL,SHIFT_MASK ;test the shift status
JNE NOT_US ;if not shift combo, exit
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 for fast AT's
OUT 61H,AL
CLI ;Disable interrupts and
MOV AL,20H ;reset the int controller
OUT 20H,AL
STI
CMP CS:BUSY,0 ;recursion protection
JNE WE_ARE_BUSY ;dont allow re-entrancy
OR CS:BUSY,INT9_BUSY ;set flag for protection
CALL ADJUST_FOR_VIDEO_MODE
JC CANT_POP_UP ;exit if inappropriate mode
CALL MAIN ;call our program
CANT_POP_UP:
CLI ;disable kbd momentarily
AND CS:BUSY,NOT(INT9_BUSY) ;reset protection
WE_ARE_BUSY:
POP AX ;restore working register
STI
IRET ;return to foreground
NOT_US:
POP AX ;restore working register
CLI ;interrupts off
JMP CS:ADDR_INT9H ;jump to original int 9
INT9H ENDP
;-----------------------------------------------------------------
; ADJUST_FOR_VIDEO_MODE
; check for text modes and set offset for lines > than 80 characters
; in length. sets carry flag if inappropriate mode for pop-up.
;-----------------------------------------------------------------
ADJUST_FOR_VIDEO_MODE PROC NEAR
PUSH BX ;save register
MOV AH,15 ;get present mode
INT 10H
CMP AH,80
JB BAD_MODE ;less than 80 chars per line
MOV CS:BYTE PTR DIFF,AH ;calc the # of chars > 80
SUB CS:BYTE PTR DIFF,80 ;on the line & save in diff
CMP AL,7 ;7 is mono, good mode
JNE TRY_COLOR
MODE_OK:
CLC ;clear carry flag
POP BX ;restore register
RET
TRY_COLOR:
CMP AL,3 ;3 is color 80x25,
JBE MODE_OK ; 2 is B&W 80x25
BAD_MODE:
STC ;not good mode, set carry flag
POP BX ;restore register
RET
ADJUST_FOR_VIDEO_MODE ENDP
;-----------------------------------------------------------------
; MAIN - main routine called by pressing hot key
;-----------------------------------------------------------------
MAIN PROC NEAR
CLD ;strings forward
CALL SWAPIN ;new stack
MOV AX,CS ;our data segment is
MOV DS,AX ; same as CS
CALL GETPOS ;save cursor position
CALL CURSOR_HOME ;cursor to 0,0
CALL SAVE_SCREEN ;save screen
CALL CLEAR_SCREEN ;clear screen
CALL PROGRAM ;construct & display memory map
MOV TABLE_FULL,0 ;reset flag
CALL RESTORE_SCREEN ;put screen back
CALL RESTORE_CURSOR ;cursor to original position
CALL SWAPOUT ;put stack back
RET ;that's all
MAIN ENDP
;-----------------------------------------------------------------
; SWAPIN, SWAPOUT - stack routines
;-----------------------------------------------------------------
SWAPIN PROC NEAR
POP CS:RETADDR ;save callers address
MOV CS:THEIR_SS,SS ;save their stack
MOV CS:THEIR_SP,SP
MOV SS,CS:OUR_SS ;switch to our stack
MOV SP,CS:OUR_SP
PUSH AX ;save all registers
PUSH BX
PUSH CX
PUSH DX
PUSH SI
PUSH DI
PUSH ES
PUSH DS
PUSH BP
JMP CS:RETADDR ;return to caller
SWAPIN ENDP
;-----------------------------------------------------------------
SWAPOUT PROC NEAR
POP CS:RETADDR ;save callers address
POP BP ;restore all registers
POP DS
POP ES
POP DI
POP SI
POP DX
POP CX
POP BX
POP AX
MOV SS,CS:THEIR_SS ;restore callers stack
MOV SP,CS:THEIR_SP
JMP CS:RETADDR ;return to caller
SWAPOUT ENDP
;-----------------------------------------------------------------
; GETPOS, CURSOR_HOME, RESTORE_CURSOR, SETPOS - cursor routines
;-----------------------------------------------------------------
GETPOS PROC NEAR
MOV AH,3 ;get cursor position
XOR BH,BH ;active page
INT 10H ;get cursor position in dx
MOV CURSOR_POS,DX ; and save
RET
GETPOS ENDP
;----------------------------------------------------------------------
CURSOR_HOME PROC NEAR
XOR DX,DX ;position 0,0
CALL SETPOS ;set cursor position
RET
CURSOR_HOME ENDP
;----------------------------------------------------------------------
RESTORE_CURSOR PROC NEAR
MOV DX,CURSOR_POS ;saved position
CALL SETPOS ;set
RET
RESTORE_CURSOR ENDP
;----------------------------------------------------------------------
SETPOS PROC NEAR
MOV AH,2 ;set cursor position
XOR BH,BH ;active page
INT 10H ;set cursor position to dx
RET
SETPOS ENDP
;-----------------------------------------------------------------
; SAVE_SCREEN, CLEAR_SCREEN, RESTORE_SCREEN - screen routines
;-----------------------------------------------------------------
SAVE_SCREEN PROC NEAR
PUSH DS ;save data segment
XOR AX,AX
MOV BX,AX
CALL CALC_SCRN_ADDR ;address of (0,0)
MOV SI,OFFSET SCREEN ;buffer is past end of table
PUSH DS ;exchange
PUSH ES ;ds and es
POP DS
POP ES
XCHG DI,SI ;exchange source,destination
MOV BX,25 ;save 25 lines
SAVE_NEXT_LINE:
MOV CX,80 ;save 80 words per line
REP MOVSW ;save line
ADD SI,CS:DIFF ;add extra characters and
ADD SI,CS:DIFF ; attributes to SI
DEC BX ;decrement line counter
JNZ SAVE_NEXT_LINE
POP DS ;restore data segment
RET
SAVE_SCREEN ENDP
;-----------------------------------------------------------------
CLEAR_SCREEN PROC NEAR
XOR AX,AX
MOV BX,AX
CALL CALC_SCRN_ADDR ;address of (0,0)
MOV AX,0720H ;space with normal attribute
MOV BX,25 ;clear 25 lines
CLEAR_NEXT_LINE:
MOV CX,80 ;clear 80 words per line
REP STOSW ;clear line
ADD DI,CS:DIFF ;add extra characters and
ADD DI,CS:DIFF ; attributes to SI
DEC BX ;decrement line counter
JNZ CLEAR_NEXT_LINE
RET
CLEAR_SCREEN ENDP
;-----------------------------------------------------------------
RESTORE_SCREEN PROC NEAR
XOR AX,AX
MOV BX,AX
CALL CALC_SCRN_ADDR ;address of (0,0)
MOV SI,OFFSET SCREEN ;buffer past end of table
MOV BX,25 ;restore 25 lines
RESTORE_NEXT_LINE:
MOV CX,80 ;restore 80 words per line
REP MOVSW ;restore line
ADD DI,CS:DIFF ;add extra characters and
ADD DI,CS:DIFF ; attributes to SI
DEC BX ;decrement line counter
JNZ RESTORE_NEXT_LINE ;25 lines
RET
RESTORE_SCREEN ENDP
;------------------------------------------------------------------
; CALC_SCRN_ADDR
; ax = row bx= col, returns es:di pointing to the screen address
;------------------------------------------------------------------
CALC_SCRN_ADDR PROC NEAR
PUSH CX ;save CX
PUSH DX ;save DX (mul destroys DX)
PUSH AX ;save AX for later
MOV ES,CS:BIOS_SEG ;bios data segment into ES
MOV AX,0B800H ;scrn seg = b800h (assume color)
CMP ES:BYTE PTR[49H],7 ;40:49 = 7?
JNZ COLOR ; no, color
MOV AH,0B0H ; yes, mono, scrn seg = b000h
COLOR:
MOV ES,AX ;scrn seg into es
POP CX ;get row
MOV AX,160 ;160 bytes to a row of text
ADD AX,CS:DIFF ;# characters > 80
ADD AX,CS:DIFF ;# of attribute bytes > 80
MUL CX ;row * 160 + diff*2
ADD AX,BX ;+col
ADD AX,BX ;row*160 + col*2
MOV DI,AX ;es:di points to right address
POP DX ;restore registers
POP CX
RET ;that's all
CALC_SCRN_ADDR ENDP
;----------------------------------------------------------------------
; PROGRAM
; Find the first MCB by scanning through memory. All MCBs have the
; character "M" as the first byte (except the last MCB, which has "Z"
; as the first byte. The second and third bytes give the segment
; address of the PSP block of the "owner" (the program which allocated
; the memory block). The fourth and fifth bytes give the length of
; the block in paragraphs. The first block is COMMAND.COM, which
; follows such things as the operating system and device drivers.
; On entry, AX=Memory block Address, BX=ES, CX=Owner.
; On exit, ES points to the first valid MCB.
;----------------------------------------------------------------------
PROGRAM PROC NEAR
XOR BX,BX ;Zero BX
SRCH_MEM:
MOV ES,BX ;Point ES to next paragraph
CMP BYTE PTR ES:[0],'M' ;Is this a MCB?
JE CHECK_MCB ; might be
CRAWL:
INC BX ;Point to next paragraph
JMP SRCH_MEM ; continue search
CHECK_MCB:
MOV AX,BX ;Point AX to next paragraph
INC AX ; (possible 1st memory block)
MOV CX,WORD PTR ES:[1] ;If first block is COMMAND.COM,
CMP AX,CX ; it will "own" itself
JNE CRAWL ;If not, continue search
FOUND_FIRST:
MOV DI,OFFSET TABLE ;Table offset in DI
; Add an entry to the table.
; If the owner=0, then this block is unallocated (free).
; AX=Mem Address, BX=ES=MCB address, CX=Owner.
; DI points to 1st empty spot in table.
CREATE_ENTRY:
INC N_BLK ;Adding new entry
MOV WORD PTR [DI],AX ;Put block addr in table
MOV WORD PTR [DI+2],CX ;Put owner in table
MOV SI,WORD PTR ES:[3] ;Put block length in
MOV WORD PTR [DI+4],SI ; table via SI
MOV SI,OFFSET SPACE3_MSG ;Blanks in type column
MOV CX,3 ;String length
ADD DI,6 ;Address in table
CALL COPY_NAME ;Move blanks to table
MOV CX,WORD PTR ES:[1] ;Owner segment back into CX
OR CX,CX ;If owner <> 0, determine
JNZ HAVE_OWNER ; type and find owner name.
MOV CX,6 ; Else set string length,
MOV SI,OFFSET FREE_MSG ; point SI to "(Free)",
CALL COPY_NAME ; and copy to table
JMP FIND_NEXT ;Next memory block
; Is this block a PSP (program) block?
HAVE_OWNER:
CMP AX,CX ;Is mem = owner?
JNE FIND_NAME ;No, not PSP block, jump
SUB DI,4 ;Yes, set table destination
MOV SI,OFFSET PSP_MSG ;Point SI to "PSP" string
MOV CX,3 ;String length
CALL COPY_NAME ;Move string to table
; If this is first block, it is COMMAND.COM.
FIND_NAME:
CMP N_BLK,1 ;If not first block
JNE FIND_ENV ; look for environment
MOV SI,OFFSET COM_MSG ;Point to "COMMAND.COM" string
MOV CX,11 ;String length
CALL COPY_NAME ;Put name in table
JMP FIND_NEXT ;Next memory block
; Word at offset 2Ch into the owner's PSP block contains the
; environment segment address.
FIND_ENV:
MOV CX,WORD PTR ES:[1] ;Owner segment into CX
MOV ES,CX ; and ES
CMP CX,WORD PTR DS:[TABLE] ;Is owner COMMAND.COM?
JNE NOT_COMMAND ;No, jump
CMP N_BLK,2 ;2nd block?
JNE NOT_ENV ;No, jump
MOV SI,OFFSET ENV_MSG ;Yes, is system environment
MOV CX,3 ;String length
SUB DI,4 ;Restore destination
CALL COPY_NAME ;Move string to table
NOT_ENV:
MOV SI,OFFSET COM_MSG ;"COMMAND.COM" to table
MOV CX,11
CALL COPY_NAME
JMP FIND_NEXT ;Next memory block
; Is this block an ENV (environment) block?
NOT_COMMAND:
MOV SI,WORD PTR ES:[2Ch] ;Get owner's env segment
CMP AX,SI ;Is this block owner's env?
JNZ EXTR_NAME ;No, jump
PUSH SI ;Save SI (env segment)
MOV SI,OFFSET ENV_MSG ;Point SI to "ENV" string
MOV CX,3 ;String length
SUB DI,4 ;Restore destination
CALL COPY_NAME ;Move string to table
POP SI ;Restore SI
; Get name from environment (if DOS 3.x or later)
EXTR_NAME:
CMP VER3,0 ;If not 3.x
JE NO_ENV ; skip this section
; Is env still allocated to owner of current block?
MOV CX,ES ;Owner segment to CX
DEC SI ;Point to env MCB
PUSH SI ;and put in DS
POP DS
CMP CX,WORD PTR DS:[1] ;Compare owners
JNZ NO_ENV ;Not our property
; The environment block terminates with two zero bytes. In DOS 3.0
; and later, the double zero is followed by a string count (two bytes)
; and the fully qualified file name of the owner program, terminated
; by a zero byte.
; Point DS:SI to the environment and scan for the double zero entry.
INC SI ;Point SI to environment
PUSH SI ; and put in DS
POP DS
XOR SI,SI ;DS:SI = ENV:0
INC SI
SCAN_ENV:
DEC SI ;Backup one byte, SI=SI-1
LODSW ;Look at word, SI=SI+2
OR AX,AX ;If not double 0 byte
JNZ SCAN_ENV ;Continue to look
; Find the end of the program pathname.
LODSW ;Skip a word (string count)
MOV BP,SI ;SI points to 1st char
DEC BP ;BP points before 1st char
SCAN_PATH:
LODSB ;Read char at SI
OR AL,AL ;If 0, end of string
JNZ SCAN_PATH ; else continue reading
; SI points past the terminating 0. Scan backwards for the \.
DEC SI ;Point SI and CX to the
MOV CX,SI ; zero byte past last char
SCAN_NAME:
DEC SI ;Point to char
CMP SI,BP ;Is it before 1st char?
JE STRING_START
CMP BYTE PTR [SI],'\' ;It is backslash?
JNE SCAN_NAME ; no, continue
STRING_START:
INC SI ;Point to start of string
SUB CX,SI ;Length of string
CALL COPY_NAME ;Transfer to table
JMP FIND_NEXT ;Next memory block
NO_ENV:
PUSH CS ;Restore DS
POP DS
MOV CX,9 ;Number of chars
MOV SI,OFFSET UNK_MSG ;Point to "Unknown" string
CALL COPY_NAME ;Transfer to table
; Point ES to next MCB and continue search. Stop at top of memory.
FIND_NEXT:
PUSH CS ;Restore DS
POP DS
CMP LAST_BLOCK,1 ;was this last block?
JE NO_MORE ; yes, done
CMP N_BLK,MAX_BLK ;out of space?
JE OUT_OF_SPACE ; yes, jump
MOV ES,BX ;ES to current MCB
ADD BX,WORD PTR ES:[3] ;BX to next MCB
INC BX
MOV ES,BX ;ES too
CMP BYTE PTR ES:[0],'Z' ;is this last block?
JNE MORE_BLOCKS ; no, jump
INC LAST_BLOCK ; yes, set flag
MORE_BLOCKS:
MOV AX,BX ;Put address of block
INC AX ; in AX
MOV DI,OFFSET TABLE ;Find
MOV CL,N_BLK ; address
XOR CH,CH ; of
ADDEM: ; next
ADD DI,23 ; table
LOOP ADDEM ; entry
MOV CX,WORD PTR ES:[1] ;Block length in CX
JMP CREATE_ENTRY ;Continue with next entry
OUT_OF_SPACE:
INC TABLE_FULL ;set flag for out of space msg
; Display the resulting table on the screen.
NO_MORE:
MOV SI,OFFSET HEADING_MSG ;Display the heading
CALL DISPLAY_STRING
MOV SI,OFFSET TABLE ;Table location
CALL PRINT_WORD ;1st table entry is address
;of COMMAND.COM = size of
;initial memory block
MOV SI,OFFSET BLOCK1_MSG ;Display 1st block description
CALL DISPLAY_STRING
MOV SI,OFFSET TABLE ;Table location
MOV CL,N_BLK ;Number of entries
XOR CH,CH ; as a word
PRINT_TABLE:
CALL PRINT_WORD ;Print address
CALL PRINT_WORD ; and owner
CALL PRINT_WORD ; and size
CALL DISPLAY_STRING ;Print type
PUSH SI ;save SI
MOV SI,OFFSET SPACE_MSG ;Space over
CALL DISPLAY_STRING
POP SI ;restore SI
ADD SI,4 ;Point to owner name
CALL DISPLAY_STRING ;and print
PUSH SI ;save SI
MOV SI,OFFSET CR_LF_MSG ;Newline
CALL DISPLAY_STRING
POP SI ;restore SI
ADD SI,13 ;point to start of next entry
;pause if CTRL-S pressed
MOV AH,1 ;keystroke waiting?
INT 16H
JZ LOOP_NOW ;no, proceed
MOV AH,0 ;get keystroke scan code
INT 16H
CMP AH,31 ;is it S?
JNE LOOP_NOW ;no, proceed
MOV AH,2 ;get shift status
INT 16H
AND AL,0FH ;mask off status of toggles
CMP AL,4 ;CTRL depressed?
JNE LOOP_NOW ;no, proceed
MOV AH,0 ;yes, wait for next keystroke
INT 16H
LOOP_NOW:
LOOP PRINT_TABLE ;print next entry
CMP TABLE_FULL,0 ;is table full?
JE DONE ; no, jump
MOV SI,OFFSET TABLE_FULL_MSG ; yes, print out of space msg
CALL DISPLAY_STRING
DONE:
MOV N_BLK,0 ;reset counter
MOV LAST_BLOCK,0 ;and flag
MOV SI,OFFSET PROGRAM_ID ;print progam ID
CALL DISPLAY_STRING
CMP TSR_MODE,1 ;TSR mode?
JNE PROGRAM_EXIT ; no, exit now
MOV SI,OFFSET HIT_ANY_KEY ; yes, print message
CALL DISPLAY_STRING
XOR AH,AH ;wait for keystroke
INT 16H
PROGRAM_EXIT:
RET
PROGRAM ENDP
;----------------------------------------------------------------------
; COPY_NAME
; Move string at DS:SI to CS:DI, string length in CX, add 0 at end
;----------------------------------------------------------------------
COPY_NAME PROC NEAR
PUSH AX ;Save AX
PUSH ES ;Save ES
PUSH CS ;Point ES to
POP ES ; this segment
REP MOVSB ;Put name in table
MOV AL,0 ;string terminator
STOSB ;Store it in table
POP ES ;Restore ES
POP AX ;Restore AX
RET
COPY_NAME ENDP
;----------------------------------------------------------------------
; PRINT_WORD - Print hex value of word at DS:SI, followed by spaces
;----------------------------------------------------------------------
PRINT_WORD PROC NEAR
LODSW ;Get value
CALL HEX4 ;Write 4 digits
PUSH SI ;save SI
MOV SI,OFFSET SPACE_MSG ;space over
CALL DISPLAY_STRING
POP SI ;restore SI
RET
PRINT_WORD ENDP
;----------------------------------------------------------------------
; HEX4 - Write AX as 4 hex digits to console
; HEX2 - Write AL as 2 hex digits to console
;-----------------------------------------------------------------------------
HEX4 PROC NEAR
PUSH AX ;Save register
MOV AL,AH ;Show high digits first
CALL HEX2 ;Display AL
POP AX ;Restore low digits in AL
HEX2 PROC NEAR ;Display AL
PUSH AX ;Save register
PUSH CX ;Save CX during shift
MOV CL,4
SHR AL,CL ;Get high 4 bits
POP CX ;Restore CX
CALL H2C ;Display upper AL digit
POP AX ;Restore lower
AND AL,0FH ;Mask and display
H2C:
ADD AL,90H ;Convert AL to ASCII
DAA
ADC AL,40H
DAA
MOV AH,0EH ;Display character
XOR BH,BH
INT 10H
RET
HEX2 ENDP
HEX4 ENDP
;------------------------------------------------------------------
; DISPLAY_STRING - displays string at ds:si
;------------------------------------------------------------------
DISPLAY_STRING PROC NEAR
PUSH SI ;save registers
PUSH AX
PUSH BX
NEXT_CHAR:
LODSB ;get character
OR AL,AL ;is it zero?
JZ LAST_CHAR ; yes, done
MOV AH,0EH ;print character
XOR BH,BH ;page 0
INT 10H
JMP NEXT_CHAR
LAST_CHAR:
POP BX ;restore registers
POP AX
POP SI
RET
DISPLAY_STRING ENDP
;----------------------------------------------------------------------
; INT10H
; this routine sets bit to prevent popping up while int 10h is active
;----------------------------------------------------------------------
INT10H PROC FAR
OR CS:BUSY,INT10_BUSY ;set bit
PUSHF ;push flags to simulate INT
CALL CS:ADDR_INT10H ;call original int 10h
PUSHF ;save flags
AND CS:BUSY,NOT(INT10_BUSY) ;clear bit
POPF ;restore flags
RET 2 ;return from int 10h
INT10H ENDP
;----------------------------------------------------------------------
; end of resident code, and start of memory used for table, screen save
; buffer, and stack. each table entry has structure:
; address dw ?
; owner dw ?
; size dw ?
; type db "XXX",0
; name db "FILENAME.EXT",0
; (total 23 bytes per entry)
;----------------------------------------------------------------------
TABLE DB (MAX_BLK*23) DUP (20H) ;reserve space for table
SCREEN LABEL BYTE ;marks start of memory used
;----------------------------------------------------------------------
; TRANSIENT DATA AREA
;----------------------------------------------------------------------
INSTALLED DB "PCMAP installed"
DB CR,LF,"Hotkey is Alt-P",CR,LF,"$"
UNINSTALLED DB "PCMAP Uninstalled",CR,LF,"$"
DISABLED DB CR,LF,"PCMAP is disabled",CR,LF,"$"
ENABLED DB CR,LF,"PCMAP is re-enabled",CR,LF,"$"
INSTALLED_SEGMENT DW 0 ;addr of resident copy
START_OFFSET DW 0 ;used by search_mem
START_SEGMENT DW 0
END_OFFSET DW 0
END_SEGMENT DW 0
SEARCH_PARAS DW 0
SEARCH_BYTES DW 0
;-----------------------------------------------------------------
; RES - code relating to residency
;-----------------------------------------------------------------
RES PROC NEAR
CLD ;strings forward
CALL CHECK_VER ;See if DOS vers >=3.0
MOV BX,80H ;ES:BX=command tail
CALL ARGV ;Get 1st argument
CMP AX,2 ;If argument length<>2,
JNE NO_RES ; proceed with program
MOV AX,ES:[BX] ;Get argument (bytes reversed)
AND AH,0DFH ;Convert to upper case
CMP AX,'R/' ;If not '/R',
JNE NO_RES ; proceed with program,
CALL PROGRAM_ALREADY_IN ; else see if already installed
JNZ NOT_IN ;if not in, it's ok to install
CALL UNINSTALL ;else, try to uninstall
MOV AX,4C00H ;terminate with error code=0
INT 21H
NO_RES:
DEC TSR_MODE ;command line mode
CALL PROGRAM ;Display memory map
MOV AX,4C00H ;terminate, assume error code=0
CMP TABLE_FULL,1 ;out of space error?
JNE RES_EXIT ; no, jump
MOV AL,01 ; yes, error code=1
RES_EXIT:
INT 21H
NOT_IN:
MOV OUR_SS,CS ;set stack seg
MOV OUR_SP,OFFSET TABLE+(MAX_BLK*23)+4000+256 ;and pointer
;(256 byte stack follows table and scrn buffer)
CALL INSTALL
MOV DX,OFFSET INSTALLED ;confirm installation
MOV AH,9
INT 21H
;program, table, scrn buf, stack, round up, cnvrt to paras
MOV DX,(OFFSET TABLE-OFFSET _TEXT+(MAX_BLK*23)+4000+256+15) SHR 4
MOV AX,3100H ;stay resident, error code=0
INT 21H
RES ENDP
;--------------------------------------------------------------------
; CHECK_VER - check DOS version
;--------------------------------------------------------------------
CHECK_VER PROC NEAR
MOV AH,30H ;Check DOS version
INT 21H ; Thru DOS
CMP AL,3 ;If not 3.x or later
JB NOT_3 ; don't turn on flag
INC VER3 ; else, indicate
NOT_3:
RET
CHECK_VER ENDP
;--------------------------------------------------------------------
; ARGV
; Call with: ES:BX = command line address
; (implicit: ES=PSP segment, BX=80h)
;
; Returns: ES:BX = argument address (first argument)
; AX = argument length
; (0=argument not found)
; Other registers preserved.
;--------------------------------------------------------------------
ARGV PROC NEAR ; get address & length of
; command tail argument
PUSH CX ; save original CX and DI
PUSH DI
ARGV1:
ARGV2: INC BX ; point to next character
CMP BYTE PTR ES:[BX],CR
JE ARGV7 ; exit if carriage return
CMP BYTE PTR ES:[BX],BLANK
JE ARGV1 ; outside argument if ASCII blank
CMP BYTE PTR ES:[BX],TAB
JE ARGV1 ; outside argument if ASCII tab
ARGV4: ; found desired argument, now
; determine its length...
MOV AX,BX ; save param. starting address
ARGV5: INC BX ; point to next character
CMP BYTE PTR ES:[BX],CR
JE ARGV6 ; found end if carriage return
CMP BYTE PTR ES:[BX],BLANK
JE ARGV6 ; found end if ASCII blank
CMP BYTE PTR ES:[BX],TAB
JNE ARGV5 ; found end if ASCII tab
ARGV6: XCHG BX,AX ; set ES:BX = argument address
SUB AX,BX ; and AX = argument length
JMP ARGVX ; return to caller
ARGV7: XOR AX,AX ; set AX = 0, argument not found
JMP ARGVX ; return to caller
ARGVX: ; common exit point
POP DI ; restore original CX and DI
POP CX
RET ; return to caller
ARGV ENDP
;------------------------------------------------------------------
; PROGRAM_ALREADY_IN - determine if program is already installed.
; returns zero flag = 1 if installed.
;------------------------------------------------------------------
PROGRAM_ALREADY_IN PROC NEAR
NOT WORD PTR START ;mark this program as active
MOV START_SEGMENT,60H ;start after dos
MOV START_OFFSET,0 ;
MOV END_SEGMENT,CS ;stop looking before you
MOV END_OFFSET,0 ; get to this program
MOV SI,OFFSET START ;start compare at modified byte
; (a previously installed copy
; will also have modified byte)
MOV CX,25 ;compare 25 bytes
CALL SEARCH_MEM ;search
PUSHF ;save zr flag
MOV AX,START_SEGMENT ;get address of find
MOV INSTALLED_SEGMENT,AX ;save in installed address
MOV AX,START_OFFSET
MOV CL,4
SHR AX,CL
SUB AX,10H ;adjust for psp
ADD INSTALLED_SEGMENT,AX
POPF ;restore flgs from search
RET
PROGRAM_ALREADY_IN ENDP
;-----------------------------------------------------------------
; SEARCH_MEM
; DS:SI = search string CX = string_size
; search for match of string beginning at START_SEGMENT:START_OFFSET,
; and ending at END_SEGMENT:END_OFFSET. if found, zero flag set,
; START_SEGMENT:START_OFFSET points to find.
;-----------------------------------------------------------------
SEARCH_MEM PROC NEAR
MOV DI,CX ;save string size
CALL END_MINUS_START ;calculate search length
LOOK_AGAIN:
CMP SEARCH_PARAS,1000H ;more than or equal 64k?
JAE MORE_THAN_ENOUGH ;if so, search 64k
MOV AX,SEARCH_PARAS ;otherwise, get what's left
MOV CL,4 ;
SHL AX,CL ;segs*16 = bytes to search
ADD AX,SEARCH_BYTES ;add in the last few bytes
JMP SHORT LOOK ;and go look
MORE_THAN_ENOUGH:
MOV AX,0FFFFh ;64K-1 bytes to search
LOOK:
SUB AX,BX ;subtract initial offset
JB SEARCH_NOT_FOUND ;offset < search size?
CMP AX,DI ;compare to string size
JB SEARCH_NOT_FOUND ;less than search size?
MOV DX,AX ;dx gets search size
MOV CL,4 ;
SHR DX,CL ;number of segments to search
SUB SEARCH_PARAS,DX ;decrease the amount to search
;si = search string di = size
;es:bx=start addr
CALL SEARCH ;ax=bytes to search
JZ SEARCH_FOUND ;if zero flag, string is found
ADD AX,1 ;next character after fail
MOV BX,AX ;into es:bx
JNC NOWR ;if offset rolls over
MOV AX,ES ;add 64k
ADD AX,1000H ;to the
MOV ES,AX ;offset
NOWR:
CALL NORMALIZE ;change ES:BX so that
; 10h > BX >= 0
JMP LOOK_AGAIN
SEARCH_NOT_FOUND:
XOR AX,AX ;start over
MOV ES,AX
CMP AL,1 ;clear zero flag
SEARCH_FOUND:
MOV START_SEGMENT,ES ;set address of found string
MOV START_OFFSET,AX
RET
SEARCH_MEM ENDP
;-----------------------------------------------------------------
; END_MINUS_START
; using START_OFFSET, START_SEGMENT, END_OFFSET, and END_SEGMENT,
; return SEARCH_BYTES, SEARCH_PARAS, and normalized pointer to
; starting address in ES:BX
;-----------------------------------------------------------------
END_MINUS_START PROC NEAR
LES BX,DWORD PTR START_OFFSET ;start addr in ES:BX
CALL NORMALIZE ;change es:bx so 10h > bx >=0
MOV AX,ES ;save normalized result
MOV CX,BX ;for later use
LES BX,DWORD PTR END_OFFSET ;get end address
CALL NORMALIZE ;change es:bx so 10h > bx >=0
MOV DX,ES ;get end segment
SUB DX,AX ;calculate paragraphs to search
MOV SEARCH_PARAS,DX ;and save
MOV SEARCH_BYTES,BX ;# bytes after final paragraph
MOV ES,AX ;set es:bx to
MOV BX,CX ; start address
RET ;that's all
END_MINUS_START ENDP
;-----------------------------------------------------------------
; NORMALIZE
; make 20 bit pointer in es:bx from segment:offset in es:bx,
; i.e. adjust ES:BX to point to same absolute address, but with
; 10h > BX >= 0
;-----------------------------------------------------------------
NORMALIZE PROC NEAR
PUSH AX ;save registers
PUSH CX
PUSH DX
MOV AX,BX ;get the offset
MOV CL,4 ;make into
SHR AX,CL ;number of paragraphs
MOV DX,ES ;get segment
ADD DX,AX ;add in number of paragraphs
MOV ES,DX ;back into segment
SHL AX,CL ;calc offset into segment
SUB BX,AX ; (BX mod 16)
POP DX ;restore registers
POP CX
POP AX
RET
NORMALIZE ENDP
;-----------------------------------------------------------------
; SEARCH
; si = search string di = string size es:bx = pointer to buffer to search
; ax = number of bytes in buffer to search. If found, zero flag set, and
; es:bx points to found string. If not found, zero flag cleared, and es:bx
; points to last first byte checked.
;-----------------------------------------------------------------
SEARCH PROC NEAR
PUSH BX
PUSH DI
PUSH SI
XCHG BX,DI ;bx=string size, es:di=ptr to data area
MOV CX,AX ;# chars in segment to search
BYTE_ADD:
LODSB ;char for first part of search
NEXT_SRCH:
REPNZ SCASB ;is first char in string in buffer
JNZ NOT_FOUND ;if not, no match
PUSH DI ;save against cmpsb
PUSH SI
PUSH CX
LEA CX,[BX-1] ;# chars in string - 1 (CX=BX-1)
JCXZ ONE_CHAR ;if one char search, we have found it
REP CMPSB ;otherwise compare rest of string
ONE_CHAR:
POP CX ;restore for next cmpsb
POP SI
POP DI
JNZ NEXT_SRCH ;if zr = 0 then string not found
NOT_FOUND:
LEA AX,[DI-1] ;ES:AX=ptr to last first character found
; (AX=DI-1)
POP SI ;restore registers
POP DI
POP BX
RET
SEARCH ENDP
;------------------------------------------------------------------
; UNINSTALL - removes resident program from memory if possible. if not,
; toggles the disable flag
;------------------------------------------------------------------
UNINSTALL PROC NEAR
CALL HOOKED_VECTORS_SAME? ;if all vectors still hooked
JZ UNINSTALL_OK ;go ahead and uninstall
MOV ES,INSTALLED_SEGMENT ;else, change the disable flag
NOT ES:DISABLE ;in the installed program
MOV DX,OFFSET ENABLED ;get the message corresponding
CMP ES:DISABLE,-1 ;to the action that causes
JNZ ITS_DISABLED ;
MOV DX,OFFSET DISABLED ;
ITS_DISABLED: ;
MOV AH,9 ;and display that message
INT 21H
JMP SHORT UNINSTALL_EXIT ;all done here.
UNINSTALL_OK:
MOV ES,INSTALLED_SEGMENT ;get resident prog's psp
NOT ES:WORD PTR START ;mark resident program inactive
MOV DX,ES:WORD PTR ADDR_INT9H ;restore int 9 vector
MOV DS,ES:WORD PTR ADDR_INT9H+2
MOV AH,25H
MOV AL,9
INT 21H
MOV DX,ES:WORD PTR ADDR_INT10H ;restore int 10h vector
MOV DS,ES:WORD PTR ADDR_INT10H+2
MOV AH,25H
MOV AL,10H
INT 21H
PUSH ES
MOV ES,ES:[2CH] ;get segment of environment
MOV AH,49H ;belonging to resident program
INT 21H ;free it
POP ES
MOV AH,49H ;free memory block of program
INT 21H
PUSH CS
POP DS ;get back our data segment
MOV DX,OFFSET UNINSTALLED ;display message
MOV AH,9
INT 21H
UNINSTALL_EXIT:
RET
UNINSTALL ENDP
;------------------------------------------------------------------
; HOOKED_VECTORS_SAME?
; determine if vectors have changed since program was installed.
; if changed, zero flag cleared; if not changed, zero flag set.
;------------------------------------------------------------------
HOOKED_VECTORS_SAME? PROC NEAR
MOV CX,INSTALLED_SEGMENT ;get executing segment
XOR AX,AX ;interrupt table segment
MOV ES,AX ;into the extra segment
CMP CX,ES:[10H*4+2] ;see if int 10h points at us
JNZ VECTOR_CHANGED
CMP CX,ES:[9*4+2] ;see if int 9 points at us
VECTOR_CHANGED:
RET
HOOKED_VECTORS_SAME? ENDP
;----------------------------------------------------------------------
; INSTALL - links vectors 9h and 10h to our code
;----------------------------------------------------------------------
INSTALL PROC NEAR
MOV CL,9 ;link vector 9
MOV SI,OFFSET ADDR_INT9H
MOV DI,OFFSET INT9H
CALL INSTALL_VECTOR
MOV CL,10H ;link vector 10h
MOV SI,OFFSET ADDR_INT10H
MOV DI,OFFSET INT10H
CALL INSTALL_VECTOR
RET
INSTALL ENDP
;----------------------------------------------------------------------
; INSTALL_VECTOR - generic vector-linking routine
;----------------------------------------------------------------------
INSTALL_VECTOR PROC NEAR
MOV AL,CL ;get vector number
MOV AH,35H ;get interrupt vector
INT 21H ;
MOV [SI],BX ;save interrupt vector
MOV [SI+2],ES ;
MOV DX,DI ;get replacement address
MOV AH,25H ;set vector address
MOV AL,CL ;for vector
INT 21H
RET
INSTALL_VECTOR ENDP
_TEXT ENDS
END START