home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Power-Programmierung
/
CD1.mdf
/
assemblr
/
library
/
showtsrs
/
showtsrs.asm
next >
Wrap
Assembly Source File
|
1988-09-29
|
63KB
|
1,173 lines
PAGE 60,132
TITLE SHOWTSRS - Program to scroll MAPMEM data
;
; Author: Tom Gilbert
; 7127 Lafayette Ave.
; Kansas City, KS
; (913) 299-2701
;
; Use Microsoft Assembler v. 5.1 or Turbo Assembler v. 1.0
; Requires DOS.INC and BIOS.INC from Microsoft Assembler package
;
; Assemble with TASM SHOWTSRS then
; Link with TLINK SHOWTSRS
; OR
; MASM SHOWTSRS then
; LINK SHOWTSRS
DOSSEG
.MODEL small
INCLUDE dos.inc ;From MASM package
INCLUDE bios.inc ; " " "
.STACK 100h
.DATA
headline DB " Allocated Memory Map - Version 1.0 - "
DB " by Tom Gilbert's Heart&Mind",13,10
DB " Syntax: > ShowTSRs"
DB " [anything for HELP]",13,10
DB " PSP MCB files bytes owner command line "
DB " chained/hooked INT vectors",13,10
DB " ---- ---- ----- ----- --------- ---------------- "
DB " --------------------------",13,10
helpdat label byte
DB " ***** ShowTSRs HELP *****",13,10
DB 13,10
DB " ShowTSRs displays the map of memory blocks and interrupts",13,10
DB " used by TurboPower Software DISABLE and RELEASE programs.",13,10,13,10
DB " PSP is the Program Segment Prefix segment address of a program",13,10
DB " or the PSP segment address for an environment of a program",13,10
DB 13,10
DB " MCB is the Memory Control Block for either of the above and is",13,10
DB " always the paragraph preceeding the controlled memory block",13,10
DB 13,10
DB " Listings show a line for each MCB. A Program's Environment is",13,10
DB ' the first of equal PSP segments. Program OPEN "files" include',13,10
DB ' the 5 standard DOS devices. Block lengths are decimal "bytes".',13,10
DB 13,10
DB " Because owner filenames are read from the end of a program's",13,10
DB " environment copy, ShowTSRs requires DOS Version 3.0 or higher!",13,10
DB ' Programs which release their environments are "command" except',13,10
DB " for TurboPower's FMARK which has another known name location.",13,10
DB 13,10
DB " Command Line Parameters are reproduced for the first 16 bytes.",13,10
DB " Those followed by an elipsis (...) exceed 16 bytes.",13,10,13,10
DB ' Interrupts which are "chained" from program to program will be',13,10
DB " displayed after WATCH is installed. Otherwise, only vectors at",13,10
DB ' the top of the chain (called "hooked" vectors) are displayed.',13,10
DB 13,10
DB " EGA Info 8 bytes and Inter-application Communication",13,10
DB " Area 16 bytes are provided in HEX & ASCII dump format.",13,10,13,10
DB " If expanded memory is installed, the Manager's Version number,",13,10
DB " Page Frame Segment (through which memory is windowed) and block",13,10
DB " information will be shown. User programs providing a name will",13,10
DB " have it displayed.",13,10
DB " ***** End of ShowTSRs Help *****",13,10
helplen equ $-helpdat
statline DB " Line: of "
stathelp DB " Move: PGUP PGDN HOME END or Use ESC key to"
statfile DB " Exit: ShowTSRs "
cmdparam DB " ",13
datf DB 0 ; Command flag 0 = Data else HELP
spsp DW ? ; Segment of ProgramSegmentPrefix
tmem DW ? ; Total Available Conventional RAM
columns EQU 80 ; Number of columns used per row
rows DW 24 ; Number of last row for display
datrows DW 20 ; Number of data rows per page
lastrow DW 24 ; Number of last display row
cell LABEL WORD ; Cell (character and attribute)
char DB " " ; Initialize to space
attr DB ? ; Attribute
mode DB ? ; Initial mode
pag DB ? ; Initial display page
newvid DB 0 ; Video change flag
cga DB 1 ; CGA flag - default yes
vidadr DW 0B800h ; Video buffer address - default CGA
mono EQU 0B000h ; Monochrome address
statatr DB 030h ; Color default - black on cyan
bwstat EQU 070h ; B&W default - black on white
scrnatr DB 017h ; Color default - white on blue
bwscrn EQU 007h ; B&W default - white on black
pbuffer DW 0 ; Position in buffer (offset)
sbuffer DW ? ; Base of buffer (segment)
lbuffer DW ? ; Length of buffer
linenum DW ? ; Data buffer line
lastnum DW ? ; Last buffer line
exkeys DB 71,72,73,79,80,81 ; Extended key codes
lexkeys EQU $-exkeys ; Table of keys
extable DW homek,upk,pgupk,endk,downk,pgdnk,nonek
EgaHdg DB " EGA Information Area at 0040:00A8 "
EgaLen equ $-EgaHdg
IcaHdg DB " Inter-application Communications Area:",13,10," 0040:00F0 "
IcaLen equ $-IcaHdg
EmsName DB "EMMXXXX0" ; EMM standard Name
tpages DW 0 ; Page accumulator
emserm DB 13,10," *** Expanded Memory NOT Installed or NOT Working ***"
emerml equ $-emserm
emmshdg DB " block pages KBytes UserName (Expanded Memory - Version "
emmlen1 equ $-emmshdg
DB ")",13,10
dashes DB " ----- ----- ------ -------- (LIM page frame address - "
emmlen2 equ $-emmshdg-emmlen1
freem DB " free"
totlm DB " total"
fmark DB "FM2.5 TSR"
envcm DB "<environment>"
doscm DB "DOSCVcommand <CONFIG.SYS>"
disam DB "*** D I S A B L E D ***"
disalen equ $-disam
WatchS DB "TSR WATCHER" ; WATCH Command Line Parameter
WatchF DW 0 ; MCB Index to WATCH PSP if Set
startl DW 0 ; Destination Index at Start of a Line
vpos DW ? ; WATCH Next PSP Position
MCB STRUC
pspa DW 0 ; Program Segment Prefix or Mark Address
mcba DW 0 ; Memory Allocation Block Address
mcbl DW 0 ; Length in paragraphs to next MCB
MCB ENDS
MCBS MCB 100 DUP (<>) ; Array of MCB Structures
.CODE
Main PROC
mov ax,@data ; Destination is data
mov es,ax ; flag with length of
mov di,OFFSET datf ; command line
mov si,80h ; parameter
movsb
mov es:spsp,ds ; Preserve PSP Segment
mov ds,ax ; Set Data Segment Register
cli ; Turn off interrupts
mov ss,ax ; Make SS and
mov sp,OFFSET STACK ; SP relative to DGROUP
sti
mov bx,sp ; Convert stack pointer to
mov cl,4 ; number of stack paragraphs
shr bx,cl
add ax,bx ; Add SS to get end of program
sub ax,spsp ; Subtract start to get length
@ModBlok ax,spsp ; Release memory after program
@GetBlok 0FFFFh ; Request all remaining memory
mov es,ax ; Set Extra Segment Register
mov sbuffer,ax ; Save buffer segment and
mov lbuffer,bx ; actual length allocated
add ax,bx ; Calculate and store total
mov tmem,ax ; available conventional RAM
mov di,pbuffer ; Point to beginning and
@GetVer ; Get DOS version
cmp al,3 ; If Version < 3.0
jc HelpOpt ; then provide HELP
test datf,0FFh ; Or If command parameter
jnz HelpOpt ; then provide HELP
call WorkMCBs ; Or If invalid MCBs
jc HelpOpt ; then provide HELP
call InfoMap ; else add info areas
mov si,OFFSET EmsName ; and EMS information
call EmmsMap ; if EMS is installed
jmp SHORT EndData
HelpOpt: mov cmdparam,"?" ; Show HELP requested
mov si,OFFSET helpdat ; and store help data
mov cx,helplen
rep movsb
EndData: call EndCount ; Count buffer
mov ax,linenum ; data lines and
mov lastnum,ax ; store the count
mov lbuffer,di ; and store length
call Video ; Adjust for mode & adapter
@SetCurPos 0,43 ; Hide cursor off screen
call homek ; Display 1st Page
mov ax,datrows ; If more data
sub ax,lastnum ; lines to show
jc nextkey ; then accept keys
dec ax ; else modify
sub lastrow,ax ; last row and
jmp SHORT quit ; exit ShowTSRs
nextkey: @GetKey 0,0,0 ; Get a key
cmp al,0 ; If a null
je extended ; then Must be extended code
cmp al,27 ; else If NOT ESCape
jne nextkey ; then Ignore unknown command
quit: @FreeBlok sbuffer ; else release buffer
cmp newvid,1 ; If video not changed
jne thatsall ; then that's all
@SetMode mode ; else Restore video mode,
@SetPage pag ; page, and cursor
thatsall: mov cx,lastrow ; Load last row and
mov ax,rows ; Calculate rows to
sub ax,cx ; be scrolled blank
xchg cl,ch ; Set Upper Left and
mov dx,cx ; copy in order to
add dh,al ; adjust Lower Right
mov dl,columns-1 ; corner of window
mov ah,6 ; Call ROM BIOS to
mov bh,7 ; clear the window
int 10h
mov dx,cx ; Set cursor above
dec dh ; window so prompt
@SetCurPos ; is on last line
@Exit 0 ; when Exit to DOS
extended: @GetKey 0,0,0 ; Get extended code
push es
push ds ; Load DS into ES
pop es
mov di,OFFSET exkeys ; Load address and
mov cx,lexkeys+1 ; length of key list
repne scasb ; Find position
pop es
sub di,(OFFSET exkeys)+1; Point to key
shl di,1 ; Adjust pointer for word addresses
call extable[di] ; Call appropriate procedure
jmp nextkey
homek: mov pbuffer,0 ; HOME - Zero the buffer
mov ax,pbuffer ; position for 1st page
jmp SHORT GoPage
upk: mov ax,-1 ; UP - GoBack one line if room
jmp SHORT GoPage
pgupk: mov ax,datrows ; PGUP - Page back
neg ax ; Up to page lines
jmp SHORT GoPage
endk: mov ax,lbuffer ; END - Get last byte of file
mov pbuffer,ax ; Make it the file position
mov ax,datrows ; Go Backward enough
neg ax ; lines for last page
jmp SHORT GoPage
downk: mov ax,1 ; GoForward 1 line if room
jmp SHORT GoPage
pgdnk: mov ax,datrows ; PGDN - Go forward <= page
GoPage: push ax
call Pager
nonek: retn ; Ignore unknown key
Main ENDP
Video PROC
push es ; Preserve Extra Segment
mov ah,12h ; Call EGA status function
mov bl,10h
sub cx,cx ; With Clear status bits
int 10h
sub ax,ax ; If status is still Clear
jcxz modechk
mov es,ax ; or if EGA is NOT active
test BYTE PTR es:[487h],1000b
jnz modechk ; then check CGA or Mono Mode
mov ax,1130h ; else get EGA information
int 10h
mov al,dl ; Make lines per screen
cbw ; into a Word Value
mov rows,ax ; Reset number of the
mov lastrow,ax ; last row and number
sub ax,4 ; of rows available for
mov datrows,ax ; data from their defaults
dec cga ; Clear the CGA Flag
modechk: pop es ; Restore Extra Segment
@GetMode ; Get video mode
mov mode,al ; Save initial
mov pag,bh ; mode and page
mov dl,al ; Work on copy
cmp dl,7 ; If mono 7
je loadmono ; then Set mono
cmp dl,15 ; else if NOT mono 15
jne graphchk ; then Check graphics
loadmono: mov vidadr,mono ; else Load mono address
mov statatr,bwstat ; Set B&W defaults for status line
mov scrnatr,bwscrn ; and screen background
dec cga ; Set as NOT CGA
cmp al,15 ; If NOT mono 15
jne VidExit ; then Done
mov dl,7 ; else Set standard mono
jmp SHORT chmode
graphchk: cmp dl,7 ; 7 or higher?
jg color ; 8 to 14 are color (7 and 15 done)
cmp dl,4 ; 4 or higher?
jg bnw ; 5 and 6 are probably black and white
je color ; 4 is color
test dl,1 ; Even?
jz bnw ; 0 and 2 are black and white
color: cmp dl,3 ; If mode 3
je VidExit ; then Done
mov dl,3 ; else use color text mode
jmp SHORT chmode
bnw: mov statatr,bwstat ; Set B&W defaults for status line
mov scrnatr,bwscrn ; and screen background
cmp dl,2 ; If mode 2
je VidExit ; then Done
mov dl,2 ; else use B&W text mode
chmode: @SetMode dl ; Set video mode
@SetPage 0 ; Set video page
mov newvid,1 ; Set flag
VidExit: ret
Video ENDP
; Procedure EndCount - Go backward to count lines in file
; Input ES:DI has buffer position
; Output Modifies "linenum"
EndCount PROC
push di
std ; Go backwards to
mov al,13 ; Search for CR
mov linenum,0 ; Initialize line count
findstrt: mov cx,0FFh ; Load maximum character count
cmp cx,di ; If NOT Near start of buffer
jl notnear2 ; then use maximum count
mov cx,di ; else search
jcxz found ; only to start
notnear2: repne scasb ; If previous CR NOT found
jcxz found ; then must be at start
inc linenum ; else adjust line count
jmp SHORT findstrt ; and continue search
found: pop di ; Restore index
cld ; and direction
ret
EndCount ENDP
; Procedure Pager - Displays status and text lines
; Input Stack variable: lines to scroll (negative up, positive down)
; Output Displays lines between first and last to screenn
Pager PROC
push bp
mov bp,sp
mov di,pbuffer ; Index to buffer position
mov cx,[bp+4] ; Get count argument for
mov ax,10 ; linefeeds to count and
or cx,cx ; If No lines to count
jz show ; then show the page
jg forward ; else Count Forward
call GoBack ; or Backward if neg
jmp SHORT show ; before showing page
forward: call GoForwd
show: call EndCount ; Count to first
mov ax,linenum ; line number to show
add ax,datrows ; Adjust to bottom line
cmp ax,lastnum ; If NOT past last
jle lineok ; then number is ok
mov ax,lastnum ; else make it last
lineok: push ds ; Set data segment into
pop es ; extra segment register
push ax ; Arg 1 - IntegerLSW
xor ax,ax
push ax ; Arg 2 - IntegerMSW
mov ax,OFFSET statline[6]
push ax ; Arg 3 - Destination
mov ax,3
push ax ; Arg 4 - Decimal Places
call BinToDStr ; Convert to string
mov ax,lastnum
push ax ; Arg 1 - IntegerLSW
xor ax,ax
push ax ; Arg 2 - IntegerMSW
mov ax,OFFSET statline[12]
push ax ; Arg 3 - Destination
mov ax,3
push ax ; Arg 4 - Decimal Places
call BinToDStr ; Convert to string
mov es,sbuffer ; Restore ES to sbuffer
mov bl,statatr ; Set attribute for
mov BYTE PTR cell[1],bl ; status & headings
xor bx,bx ; Initialize counter
mov si,OFFSET headline ; for heading lines
hdloop: push bx ; Preserve counter
push ds ; Arg 1 - Segment
push si ; Arg 2 - Offset
push bx ; Arg 3 - Display Line
push cell ; Arg 4 - Char/Attrib
call CellWrt ; Write one
push ss ; Restore DGroup
pop ds ; into DS register
pop bx ; Restore line count and
mov si,ax ; get returned position
inc bx ; Count the heading line
cmp bx,4 ; If NOT yet 4 lines
jc hdloop ; then loop until 4
mov al,scrnatr ; Change attribute for
mov BYTE PTR cell[1],al ; data buffer display
mov si,pbuffer ; Index to pbuffer
datloop: push bx ; Preserve counter
push sbuffer ; Arg 1 - Segment
push si ; Arg 2 - Offset
push bx ; Arg 3 - Display Line
push cell ; Arg 4 - Char/Attrib
call CellWrt ; Write line
push ss ; Restore DGroup
pop ds ; into DS register
pop bx ; Restore counter and
inc bx ; Count row displayed
cmp ax,lbuffer ; If position => end
jnc pagedone ; then page is done
mov si,ax ; else update pointer
cmp bx,rows ; If short of last row
jc datloop ; then loop Until done
pagedone: mov al,statatr ; Load attribute for
mov BYTE PTR cell[1],al ; writing status line
mov si,OFFSET statline
push ds ; Arg 1 - Segment
push si ; Arg 2 - Offset
push bx ; Arg 3 - Display Line
push cell ; Arg 4 - Char/Attrib
call CellWrt ; Write status line
mov es,sbuffer ; Restore ES to buffer
pop bp ; Discard stack
ret 2 ; count argument
Pager ENDP
; Procedure Retrace
; Purpose Writes cell during horizontal retrace (CGA)
; Input ES:DI has screen buffer position, AX has cell
; Output Character to screen buffer
Retrace PROC
push bx
mov bx,ax ; Save character
lscan2: in al,dx ; Look in the port
shr al,1 ; until it goes low
jc lscan2
cli
hscan2: in al,dx ; Look in the port
shr al,1 ; until it goes high
jnc hscan2
mov ax,bx ; Restore and write it
stosw
sti
pop bx
ret
Retrace ENDP
; Procedure CellWrt - Writes a line to screen buffer
; Input Stack variables (segment,offset,line,cell)
; Output Line to screen buffer
CellWrt PROC
push bp
mov bp,sp
sub dx,dx ; Clear as flag for scan
cmp cga,1 ; CGA?
jne noscan
mov dx,03DAh ; Load port #
noscan: mov es,vidadr ; Load screen buffer segment
mov ds,[bp+10] ; Buffer segment
mov si,[bp+8] ; Buffer position
mov cx,80 ; Cells per row
mov ax,[bp+6] ; Starting row
mov bx,80*2 ; Bytes per row
mul bl ; Figure columns per row
mov di,ax ; Load as destination
mov ax,[bp+4] ; Set Attribute
movechar: lodsb ; Get character
cmp al,13 ; If End of Data Line
je fillspc ; then end display line
or dx,dx ; else if NOT CGA
je notCGA ; then Write without delay
call Retrace ; else Write during retrace
loop movechar ; until End of Data Line
jmp SHORT nextline ; or end of display line
notCGA: stosw
loop movechar ; If end of display line
jmp SHORT nextline ; then find End of Data Line
fillspc: mov al," " ; Fill with space
or dx,dx ; If NOT CGA
je space2 ; then direct
space1: call Retrace ; else Write during retrace
loop space1 ; until end of display line
inc si ; Adjust for Data line LF
jmp SHORT exit ; Done
space2: rep stosw ; Write
inc si ; Adjust for LF
jmp SHORT exit ; Done
nextline: mov ah,10 ; Search for Data line feed
chklf: lodsb ; Load and compare
cmp al,ah ; If NOT Data Line LF
loopne chklf ; then contine until
exit: mov ax,si ; Return position
pop bp
ret 8
CellWrt ENDP
; Procedure Search Backward or Forward through buffer
; Input CX has number of lines; ES:DI has buffer position
; Output Updates "pbuffer" and DI index
GoBack PROC
std ; Go backward
neg cx ; Make count positive
inc cx ; Use one extra going up
findb: push cx ; Preserve counter
mov cx,0FFh ; Load maximum character count
cmp cx,di ; If NOT near start of buffer
jc scanb ; then use maximum count
mov cx,di ; else search only to start
scanb: repne scasb ; If previous LF NOT found
jcxz atstart ; then must be at start
pop cx ; else loop until start/done
loop findb
add di,2 ; Adjust for cr/lf
jmp SHORT GoBackX ; Return position
atstart: pop cx
sub di,di ; Set index and
GoBackX: mov pbuffer,di ; pointer and
ret ; Return position
GoBack ENDP
GoForwd PROC
cld ; Go forward
findf: mov pbuffer,cx ; Preserve count
mov cx,0FFh ; Load maximum character count
repne scasb ; If next LF NOT found
jcxz atend ; then must be at end
mov cx,pbuffer ; else If past end
cmp di,lbuffer ; then make at end
jae atend ; else loop until
loop findf ; at end or found
mov pbuffer,di
call EndCount ; Get line number
mov cx,lastnum ; If last number
sub cx,datrows ; minus display
cmp cx,linenum ; is => linenum
jnc GoForX ; then pbuffer Ok
atend: mov di,lbuffer ; Set index to end
mov cx,datrows ; Set page lines to
neg cx ; back-up during
mov al,10 ; GoBack procedure
call GoBack
GoForX: ret ; Return pbuffer
GoForwd ENDP
; Procedure BinToDStr Converts integer to right-justified decimal string
; Input Stack arguments: (integerLSW,integerMSW,near-address,places)
; Output BX:DX has leading:significant places written
BinToDStr PROC
push bp
mov bp,sp
mov ax,[bp+10] ; Arg 1 (LSW)
mov dx,[bp+8] ; Arg 2 (MSW)
mov di,[bp+6] ; Arg 3 (addr)
sub cx,cx ; Clear counter
mov bx,10 ; Divide by 10
getdigit: div bx ; Get last digit as remainder
add dl,"0" ; Convert to ASCII
push dx ; Save on stack
sub dx,dx ; Clear top
or ax,ax ; Until Quotient
loopnz getdigit ; becomes zero
neg cx ; Negate and
mov bx,cx ; save count
mov dx,[bp+4] ; Arg 4 (places)
sub dx,bx ; If <= 0 to go
jle putdigit ; then abort
mov cx,dx ; else fill leading
or al," " ; places with spaces
rep stosb
mov cx,bx ; Restore count
putdigit: pop ax ; Add digit
stosb ; characters
loop putdigit
mov ax,[bp+4] ; Return digit counts
sub ax,bx ; leading/significant
pop bp ; Discard stack
ret 8 ; parameters
BinToDStr ENDP
Val2ASCh PROC
mov ah,al ; Preserve byte value
and al,0F0h ; Isolate high
shr al,1 ; nibble
shr al,1 ; into
shr al,1 ; low
shr al,1 ; nibble
call Val2Dig ; Convert to and
stosb ; store ASCII HEX
mov al,ah ; Restore byte value
and al,0Fh ; Isolate low nibble
Val2Dig: add al,30h ; Convert to display
cmp al,3Ah ; If decimal digit
jc V2DX ; then ASCII numeral
add al,7 ; else make HEX alpha
V2DX: ret
Val2ASCh ENDP
PgsAndKbs PROC
push ax ; Preserve PagesLSW
xor dx,dx ; Clear PagesMSW
mov bx,9 ; Set digit places
push ax ; Arg 1 - PagesLSW
push dx ; Arg 2 - PagesMSW
push di ; Arg 3 - destination
push bx ; Arg 4 - digit places
call BinToDStr ; Store decimal pages
pop ax ; Restore PagesLSW
xor dx,dx ; Clear Extension
mov bx,16 ; Convert Pages to
mul bx ; KiloBytes LSW & MSW
mov bx,9 ; Set digit places
push ax ; Arg 1 - KiloByteLSW
push dx ; Arg 2 - KiloByteMSW
push di ; Arg 3 - destination
push bx ; Arg 4 - digit places
call BinToDStr ; Store decimal KiloBytes
ret
PgsAndKbs ENDP
SortMCBs PROC
push cx ; Preserve PSP Counter
push bx ; and MCB Index Pointer
dec cx ; Set Compare Counter
SLoop: add bx,6 ; Advance MCB Index
mov ax,MCBS[bx].mcbl ; Store
mov MCBS.mcbl,ax ; length
mov ax,MCBS[bx].mcba ; MCB
mov MCBS.mcba,ax ; and
mov ax,MCBS[bx].pspa ; PSP addresses in
mov MCBS.pspa,ax ; base array member
cmp ax,MCBS[bx+6].pspa ; If PSPs Ascending
jle LoopS ; then loop until done
mov ax,MCBS[bx+6].pspa ; else
mov MCBS[bx].pspa,ax ; swap
mov ax,MCBS[bx+6].mcba ; the
mov MCBS[bx].mcba,ax ; data
mov ax,MCBS[bx+6].mcbl ; for
mov MCBS[bx].mcbl,ax ; the
mov ax,MCBS.mcbl ; two
mov MCBS[bx+6].mcbl,ax ; array
mov ax,MCBS.mcba ; members
mov MCBS[bx+6].mcba,ax ; that
mov ax,MCBS.pspa ; were
mov MCBS[bx+6].pspa,ax ; compared
LoopS: loop SLoop ; until all compared
mov al," " ; Use Spaces to
mov cx,lbuffer ; fill data buffer
push di ; Preserve pointer
rep stosb ; before filling and
pop di ; Restore Pointer
pop bx ; Restore MCB Index
pop cx ; and PSP Counter
ret ; MCBS[0] last PSP
SortMCBs ENDP
IsEnviron PROC
mov cx,MCBS[bx].mcba ; Convert Environment
inc cx ; MCBA to Environment
mov es,cx ; Set-Up Segment:Index to
xor di,di ; search through
mov ax,MCBS[bx].mcbl ; Environment Length
mov cx,4 ; multiplied by 16 to
shl ax,cl ; convert to bytes
sub cl,4 ; for a double null
xchg ax,cx
SearchL: repne scasb ; If counter runs out
jcxz NoFname ; then NOT environment
dec cx ; else if double-null
scasb ; is NOT found before
jcxz NoFname ; counter has NOT run out
jne SearchL ; then loop until either
mov al,"." ; Search for an extent
repne scasb ; If extent NOT found
jne NoFname ; then copy "DOScommand"
sub di,2 ; else isolate filename
mov cx,10 ; Set Owner Area Length
FnameLp: cmp BYTE PTR es:[di],":"; If character
jz NameEnd ; is drive
cmp BYTE PTR es:[di],"\"; or directory
jz NameEnd ; then filename done
dec di ; else backup to
loop FnameLp ; next character
NoFname: push ds ; Put Data Segment into
pop es ; Extra Segment Register
mov di,OFFSET doscm+2 ; Point short of "DOScommand"
NameEnd: inc di ; Point to 1st
mov si,di ; source character
push ds ; Preserve Data Segment
push es ; Transfer ES after
mov es,sbuffer ; Restoring Buffer Segment
pop ds ; into DS Register and
mov di,bp ; Restore MapData Pointer
mov dx,10 ; Calculate
sub dx,cx ; filename
xchg dx,cx ; length and
rep movsb ; store Owner and
add di,dx ; space to command line
pop ds ; Restore Data Segment
mov si,OFFSET envcm ; Point to "<environment>"
mov cx,13 ; Store its length
rep movsb ; into command line and
add di,6 ; advance to vectors
ret
IsEnviron ENDP
IsProgram PROC
push ax ; Preserve PSP and
push bx ; MCBS Index Pointer
sub bx,6 ; Backup to Environment MCB
call IsEnviron ; Get Owner Information
mov cx,19 ; Backup to
sub di,cx ; Command and
mov al," " ; Space-It-Out
rep stosb
sub di,20 ; Restore Data
pop bx ; Pointer, MCBS
pop ax ; Index and PSP
ret
IsProgram ENDP
OwnComVec PROC
push cx ; Preserve StoLoop Counter
inc di ; Advance and save
mov bp,di ; pointer to Owner
mov ax,MCBS[bx].pspa ; Get this MCB's PSP
cmp bx,24 ; If MCB => 4th
jnc CkEnvir ; then check if Environment
cmp ax,MCBS[bx-6].pspa ; else if same as last PSP
je IsEnvir ; then IS DOS Environment
cmp ax,8 ; else if NOT CONFIG.SYS
jne Ck4Mark ; then fall through to command
mov si,OFFSET doscm ; else IS DOS configuration
mov cx,3 ; copy
rep movsb ; "DOS"
add di,7 ; Advance
add si,10 ; Pointers
mov cx,12 ; copy
rep movsb ; "<CONFIG.SYS>"
jmp OCVExit ; and End the Line
IsEnvir: mov si,OFFSET doscm+5 ; Owner is
mov cx,7 ; "command"
rep movsb ; copy and
add di,3 ; Advance
mov cx,13 ; pointer for
mov si,OFFSET envcm ; "<environment>"
rep movsb ; as command line
jmp OCVExit ; and End the Line
CkEnvir: cmp ax,MCBS[bx+6].pspa ; If NOT same as next
jne CkYour6 ; then check behind
call IsEnviron ; else IS Environment
jmp SHORT OCVExit
CkYour6: cmp ax,MCBS[bx-6].pspa ; If NOT same as last
jne Ck4Mark ; then check for FMark
call IsProgram ; else IS Program PSP
push ds ; Preserve Data Segment
mov ds,ax ; Set to PSP and
jmp SHORT CmdParm ; Get Command Line
Ck4Mark: push ds ; Preserve Data Segment
mov es,ax ; Point into PSP at
mov di,60h ; FMark signature area
mov si,OFFSET fmark ; If FMark
mov cx,9 ; signature
rep cmpsb ; bytes match
je IsFMark ; then is FMark
pop ds ; else Restore Data and
mov es,sbuffer ; MapData Buffer Segments
mov di,bp ; Restore MapData Pointer
mov si,OFFSET doscm+5 ; Point to "command"
mov cx,7 ; bytes and copy to
rep movsb ; Owner Area of MapData
add di,2 ; Advance to Command Line
push ds ; Preserve Data Segment
mov ds,ax ; Set to PSP and
jmp SHORT CmdParm ; Get Command Line
IsFMark: push es ; Put PSP Segment AFTER
mov es,sbuffer ; Restore MapData Buffer
pop ds ; into DS Register
mov si,di ; Set Source Index to
mov cx,9 ; beginning of the
sub si,cx ; FMark signature
mov di,bp ; Segment and Pointer
rep movsb ; Copy FMark Signature
CmdParm: mov si,80h ; Point to Command Length
lodsb ; Convert Parameter
cbw ; Length to Word
mov cx,19 ; Set length to Vectors
xchg ax,cx ; and length of Command
sub ax,cx ; Calculate difference
cmp cx,16 ; If command <= 16
jle CopyCmd ; then copy all bytes
mov cx,16 ; else copy 16 bytes
mov ax,".." ; adding continuation
CopyCmd: rep movsb ; If copied parameter
cmp ax,".." ; is NOT continuation
jne Go2Vecs ; then adjust to Vectors
stosw ; else use continuation
stosb ; elipsis (...) and
xor ax,ax ; no further spaces
Go2Vecs: add di,ax ; Adjust DI to Vectors
pop ds ; Restore Data Segment
mov ax,MCBS[bx].mcba ; If Memory Control Block
inc ax ; Segment Address + 1
cmp ax,MCBS[bx].pspa ; is NOT EQUAL to PSP
jne OCVExit ; then NO Interrupts
call Vectors ; else store vectors
OCVExit: mov ax,0A0Dh ; End the Data
stosw ; Storage Line
pop cx ; Restore StoLoop Counter
ret
OwnComVec ENDP
WorkMCBs PROC
mov ah,52h ; Use reserved DOS
int 21h ; Interrupt to get
mov bx,es:[bx-2] ; Start MCB Address
xor cx,cx ; Zero Array Counter
MCBLoop: mov es,bx ; Locate MCB Segment
mov bx,es:[3] ; Input length to next
mov dx,es:[1] ; from PSP Address
or dx,dx ; If NO PSP Address
jz CkBlock ; then check MCB ID
inc cx ; else advance counter
mov ax,6 ; calculate
mul cl ; and set
mov bp,ax ; MCB index
mov MCBS[bp].pspa,dx ; Store PSP Address
mov MCBS[bp].mcba,es ; MCB Address and
mov MCBS[bp].mcbl,bx ; Length to Next MCB
CkBlock: cmp BYTE PTR es:[0],"Z" ; If Last MCB
je LastMCB ; then MCBs done
cmp BYTE PTR es:[0],"M" ; else if Next MCB
je NextMCB ; then process MCB
mov es,sbuffer ; else Restore Buffer
stc ; Segment and Exit
jmp ExitMCB ; with CY flag set
NextMCB: mov dx,es ; If MCB address
add bx,dx ; plus length to
inc bx ; next from PSP is before
cmp bx,spsp ; segment of current PSP
jc MCBLoop ; then loop until there
LastMCB: mov es,sbuffer ; else Restore Buffer Segment
xor bx,bx ; Initialize MCB Index Pointer
call SortMCBs ; Sort by PSP and space buffer
StoLoop: add bx,6 ; Advance MCB Index
mov startl,di ; UpDate Start of Line
inc di ; Start with a space
mov ax,MCBS[bx].pspa ; Get PSP Address Word
push ax ; Preserve LSB while
mov al,ah ; isolate MSB and
call Val2ASCh ; store 1st MSB and
stosb ; 2nd HEX ASCII digits
pop ax ; Restore LSB and
push ax ; Preserve for decision
call Val2ASCh ; Store 1st LSB and
stosb ; 2nd HEX ASCII digits
inc di ; plus a space
mov ax,MCBS[bx].mcba ; Get MCB Address Word
push ax ; Preserve LSB while
mov al,ah ; isolate MSB and
call Val2ASCh ; store 1st MSB and
stosb ; 2nd HEX ASCII digits
pop ax ; Restore LSB and
call Val2ASCh ; store 1st LSB and
stosb ; 2nd HEX ASCII digits
pop ax ; If PSP
cmp ax,MCBS.pspa ; Was Last
jnc WasLast ; then End
push cx ; else Preserve StoLoop
push bx ; counter and MCBS Index
mov bx,MCBS[bx].mcba ; If the MCB
inc bx ; plus one
cmp ax,bx ; equals PSP
jz FCounts ; then count
add di,4 ; else advance pointer
jmp SHORT NoFileX
FCounts: mov bp,di ; Preserve MapData Pointer
mov es,ax ; Point to Segment and
mov di,18h ; Offset of DOS Files
mov cx,20 ; Initialize Counter
mov al,0FFh ; Looking for closed
repne scasb ; Preserve position
mov ax,di ; after search
mov es,sbuffer ; Restore Data Buffer
mov di,bp ; Segment and Pointer
sub ax,19h ; Calculate open files
xor dx,dx ; as a double word
mov bx,4 ; Set number of places
push ax ; Arg 1 - LSW
push dx ; Arg 2 - MSW
push di ; Arg 3 - dest
push bx ; Arg 4 - places
call BinToDStr ; Store number of files
NoFileX: pop bx ; Restore Index and
pop cx ; StoLoop Counter
inc di ; Advance to end of files
mov ax,MCBS[bx].mcbl ; Store length as
jmp SHORT P2Bytes ; decimal bytes
WasLast: neg ax ; Calculate
add ax,tmem ; free memory
mov si,OFFSET freem+1 ; Store " free"
mov cx,5 ; memory bytes
rep movsb ; Counter now 0
P2Bytes: push cx ; Preserve Counter
push bx ; and MCB Index
xor dx,dx ; Clear top and
mov bx,10h ; multiply into
mul bx ; double word bytes
mov bx,7 ; Set for 7 place
push ax ; integerLSW and
push dx ; integerMSW to
push di ; store into
push bx ; the data
call BinToDStr
pop bx ; Restore Index and
pop cx ; If Counter is zero
jcxz WorkEnd ; then work is done
call OwnComVec ; else finish line
jmp StoLoop ; Until Last PSP
WorkEnd: mov ax,0A0Dh ; End the
stosw ; Last Line
ExitMCB: ret
WorkMCBs ENDP
DoIMdata PROC
push ds ; Preserve Data Segment
push ax ; and Pointer to DOS Data
mov si,ax ; Initialize Source Index
mov cx,8 ; Pointer and Counter
mov ax,40h ; Set DOS data segment in
mov ds,ax ; Data Segment Register
cmp si,0A8h ; If EGA Info Area
jz IMAOk ; then bytes IS 8
add cx,8 ; else bytes is 16
IMAOk: push cx ; Preserve byte counter
IMdigL: inc di ; Space before
lodsb ; data byte's
call Val2ASCh ; first and
stosb ; 2nd HEX ASCII digits
loop IMdigL ; until count complete
pop cx ; Restore byte counter
pop si ; and DOS data pointer
add di,2 ; Add 2 spaces
cmp si,0A8h ; If NOT 8 byte EGA
jnz IMascL ; then ready for ASCII
add di,8 ; else need 8 spaces
IMascL: lodsb ; Get a byte
cmp al,20h ; If => space
jnc CkHigh ; then check delete
UseDot: mov al,"." ; else use a dot
CkHigh: cmp al,7Fh ; If => delete
jnc UseDot ; then use a dot
stosb ; Send to MapData
loop IMascL ; until CX 'em
pop ds ; Restore Data Segment
mov ax,0A0Dh ; End the line
stosw
ret
DoIMdata ENDP
InfoMap PROC
call Underline ; Underline block data
mov si,OFFSET EgaHdg ; Transfer EGA Info
mov cx,EgaLen ; Area Heading
rep movsb
mov ax,0A8h ; Point to and
call DoIMdata ; transfer EGA data
mov si,OFFSET IcaHdg ; Transfer Inter-
mov cx,IcaLen ; Application Area
rep movsb ; Heading bytes
mov ax,0F0h ; Point to and
call DoIMdata ; get ICA data
Underline: mov ax,"- "
stosb ; Space plus
mov al,ah ; Minus sign
mov cx,76 ; Underlines
rep stosb
mov ax,0A0Dh ; End the
stosw ; underline
ret
InfoMap ENDP
EmmsMap PROC
mov ax,3567h ; Get Vector for
int 21h ; Function 67hex
push di ; Preserve store pointer
mov di,000Ah ; If Device
mov cx,8 ; Name is NOT
rep cmpsb ; "EMMXXXX0"
mov es,sbuffer ; after restore
pop di ; storage ES:DI
jne EmsErrX ; then Error Exit
mov ah,46h ; or if version
int 67h ; number request
or ah,ah ; returns error
jnz EmsErrX ; then Error Exit
mov si,OFFSET emmshdg ; else store 1st
mov cx,emmlen1 ; heading line
rep movsb ; with Version
call Val2ASCh ; Major Number
mov ah,"." ; plus dot and
xchg al,ah ; Minor Number
stosw
mov cx,emmlen2 ; Add 2nd heading
rep movsb ; line lead-in to
mov ah,41h ; EMS Page Frame
int 67h ; If Page Frame
or ah,ah ; Request Fails
jnz EmsErrX ; then Error Exit
mov al,bh ; else store HEX
call Val2ASCh ; digits one and
stosb ; two and follow
mov al,bl ; with the third
call Val2ASCh ; and fourth plus
mov ah,")" ; ending parenthesis
stosw
mov ax,0A0Dh ; End the line
stosw
mov ah,4Bh ; Get Handle
int 67h ; Count in BX
or ah,ah ; If Response
jz EmPages ; then Map Pages
EmsErrX: mov si,OFFSET emserm ; else store
mov cx,emerml ; E M S
rep movsb ; Error
jmp SHORT EmmExit ; Message
EmPages: mov cx,bx ; Set Handle Counter
inc cx ; for zero thru [bx]
xor dx,dx ; Count up from 0
HndLoop: mov ah,4Ch ; Get Assigned
int 67h ; Handle Pages
or ah,ah ; If Error
jnz NoPages ; then skip
or bx,bx ; else if > 0
jnz PagesOk ; then store
NoPages: inc dx ; else loop until
loop HndLoop ; CX handles done
jmp SHORT HndExit
PagesOk: push dx ; Preserve Handle
push cx ; Handle Counter
push bx ; and Handle Pages
mov cx,6 ; Set places
xor ax,ax ; and MSW
push dx ; Arg 1 - LSW
push ax ; Arg 2 - MSW
push di ; Arg 3 - destination
push cx ; Arg 4 - places
call BinToDStr ; Store Handle Number
pop ax ; Restore Pages and
add tpages,ax ; accumulate total
call PgsAndKbs ; Store Pages and KiloBytes
pop cx ; Restore Counter
pop dx ; and EMS Handle
add di,3 ; else Advance to
mov ax,5300h ; UserName Start to be
int 67h ; Stored If Available
add di,8 ; Advance Past Area
HndlEnd: mov ax,0A0Dh ; End the line
stosw
inc dx ; Increment Handle
loop HndLoop ; until CX'em done
HndExit: mov ah,42h ; Get Free
int 67h ; Pages
mov dx,tpages ; Calculate
add dx,bx ; Total Pages
mov si,OFFSET freem ; Store
mov cx,6 ; " free"
rep movsb ; lead-in
push dx ; Preserve Total
mov ax,bx ; Store Free as
call PgsAndKbs ; Pages and KiloBytes
mov si,OFFSET dashes+24 ; Space Over
mov cx,11 ; and dash-out
rep movsb ; UserName
mov ax,0A0Dh ; End the line
stosw
mov si,OFFSET totlm ; Store
mov cx,6 ; " total"
rep movsb ; lead-in
pop ax ; Store Total as
call PgsAndKbs ; Pages and KiloBytes
mov si,OFFSET dashes+24 ; Space Over
mov cx,11 ; and dash-out
rep movsb ; UserName
EmmExit: mov ax,0A0Dh ; End the line
stosw
ret
EmmsMap ENDP
Vectors PROC
mov si,OFFSET WatchS ; else if last
push di ; command line
sub di,19 ; parameter was
mov cx,11 ; "TSR WATCHER"
rep cmpsb ; then WATCH is
pop di ; installed
jnz CkWatch ; else check flag
mov WatchF,ax ; Set Watch PSP as Flag
CkWatch: cmp WatchF,0 ; If NO TSR WATCHER Installed
jz UseHook ; then Hooked else Chained Vectors
push ds ; Preserve Data Segment
mov ds,WatchF ; while Point to Watch
mov dx,ax ; Copy Program PSP
mov si,104h ; Get Next Vector
lodsw ; Position in
mov si,220h ; Vector Change
add ax,si ; Storage Area
mov vpos,ax ; Store for Comparison
mov ax,dx ; Restore PSP and Zero
xor bp,bp ; Vector/Line Counter
FFLoop: cmp si,vpos ; If at Table End
jz WatchX ; then exit done
lodsw ; else if Word
cmp ax,-1 ; is NOT pspid
jne FFLoop ; then keep looking
lodsw ; or if Program PSP
cmp ax,dx ; is NOT in next word
jne FFLoop ; then keep looking
add si,4 ; else Point to Vectors
WatchL: lodsw ; If Next pspid
cmp ax,-1 ; is found
jz WatchX ; then exit done
cmp ah,0 ; else if Case ID = 0
jz WatchO ; then check columns Ok
cmp bp,0 ; else if Vectors Written
jnz WatchX ; then exit done
pop ds ; else Restore DS
mov si,OFFSET disam ; and store "***
mov cx,disalen ; D I S A B L E D
rep movsb ; ***" and exit
jmp SHORT INTExit
WatchO: cmp bp,9 ; If NOT to last column
jc WatchW ; then store Vector
mov WORD PTR es:[di],0A0Dh
add di,53 ; else start new line
xor bp,bp ; and update counter
WatchW: call Val2ASCh ; Store 2 HEX ASCII
mov ah," " ; digits plus a space
stosw
inc bp ; Count Vector
add si,6 ; Advance to next
jmp SHORT WatchL ; vector until exit
WatchX: pop ds ; Restore Data Segment
jmp SHORT INTExit
UseHook: mov bp,di ; else copy Pointer
xor di,di ; Point ES:DI to
mov es,di ; DOS INT Vectors
mov cx,512 ; Set Word Count
mov dx,4 ; and INT Divisor
INTLoop: mov ax,MCBS[bx].pspa ; Scan for PSP in
repne scasw ; DOS Vector Table
mov es,sbuffer ; Restore ES:DI to Buffer
xchg bp,di ; If at End of Vector Table
jcxz INTExit ; then Vectors are Done
mov ax,bp ; else Calculate
div dl ; Vector Number
dec ax ; Zero - Based
call Val2ASCh ; Display 2 HEX ASCII
mov ah," " ; digits plus a space
stosw
xor ax,ax ; Reset Extra Segment
mov es,ax ; and Pointer to Vectors
xchg bp,di ; preserving MapData Pointer
mov ax,startl ; If start of current row
add ax,columns-3 ; to position after end
cmp bp,ax ; is greater than pointer
jc INTLoop ; then loop until end/done
mov WORD PTR es:[bp],0A0Dh
add bp,2 ; else start new line
mov startl,bp ; mark start of line
add bp,51 ; Advance to Vector Area
jmp SHORT INTLoop ; Loop Until Vectors Done
INTExit: ret
Vectors ENDP
END Main