home *** CD-ROM | disk | FTP | other *** search
- ;WATCH.ASM
- ;resident routine watches programs going resident
- ;and keeps a list of interrupt vector changes in an internal data structure
- ;==============================================================================
- ; written for TASM
- ; Copyright (c) 1986,1991 Kim Kokkonen, TurboPower Software.
- ; May be freely distributed but not sold except by permission.
- ; telephone: 719-260-6641, Compuserve 76004,2611
- ;==============================================================================
- ; VERSION 2.2 3/4/87
- ; First release, version to be consistent with MAPMEM.PAS
- ; :
- ; long intervening history
- ; :
- ; VERSION 3.0 9/24/91
- ; add tracking for TSRs that unload themselves
- ; add support for TSRs loaded high
- ; WATCH may be loaded high
- ;==============================================================================
- ;
- Cseg segment public para
- assume cs:Cseg, ds:nothing, es:nothing, ss:nothing
-
- org 080H
- cmdline label byte ;pointer to command line
-
- org 100H
- comentry:
- jmp init
-
- ;put the following in WATCH.MAP to update MEMU.PAS
- public bmesg,changevectors,origvectors,currvectors,nextchange
-
- ;the following are useful when debugging
- ;public newint16,setup,shutdown,pspmatch,pspremove,dealloc
- ;public checkvec,vechdr,wrchg,cmpvec,savevec
- ;public stb21,stb27,st21idx,st27idx
-
- ;******************************************************************************
- ;resident data structures not part of COM file
- changevectors = offset bmesg ;data area overwrites bmesg & beyond
- vrecsize equ 8 ;number of bytes per vector change record
- maxchanges equ 128 ;maximum number of vector changes
- vsize equ maxchanges*vrecsize ;size of vector change area in bytes
-
- ;vector table buffers
- origvectors equ offset changevectors+vsize ;location of original vector table
- veclen equ 400H ;size of vector table in bytes
- currvectors equ origvectors+veclen ;location of current vector table
- newstackpos equ currvectors+veclen ;location of newstack
- ssize equ 0080H ;number of bytes in temporary stack
- newloc equ newstackpos+ssize ;location for relocated installation code
-
- ;******************************************************************************
- ;data structures part of COM file
- even
- nextchange dw 0 ;next position to write in data area
- ourcs dw ? ;value of cs at runtime
-
- ;temporary stack used by interrupt handler
- newss dw ? ;segment of our temporary stack
- newsp dw ? ;initial stack pointer
- tmpret dw ? ;used while switching stacks
-
- ;information saved about the calling program
- oldss dw ? ;stack segment
- oldsp dw ? ;stack pointer
-
- ;previous interrupt handlers
- kbd_int label dword
- old16 dw 2 dup (?) ;old int16 vector
- dos_int label dword
- old21 dw 2 dup (?) ;old int21 vector
-
- ;int16H function call for id check
- getid equ 'wa' ;function code for int16
- chkid equ 'WA' ;returned by int16 getid check
-
- ;id code for a PSP data block
- pspid equ 0FFFFH ;id used to indicate a PSP block
-
- ;***********************************************************************
- ;interrupt handler for int16
- ;used only to avoid reinstallation
- newint16 proc near
- assume ds:nothing
- pushf ;save application flags
- sti
- cmp ax,getid ;see if our id function
- jne ex16 ;no, pass on to previous int16
- mov ax,chkid ;return id code
- popf
- iret ;back to caller
- ex16: popf
- jmp kbd_int ;transfer control to the previous int16
- newint16 endp
-
- ;***********************************************************************
- ;int 21 handling stubs
- ;code counts on exact byte sequence of each stub
- st21siz equ 8 ;number of bytes in int 21 stub
- st21max equ 32 ;maximum times we can grab int 21
- st21idx dw offset stb21 ;offset of current stub in use
- st21lim dw offset stb21+st21siz*(st21max-1) ;last usable stub
-
- stb21 label byte
- REPT st21max
- assume ds:nothing
- call int21work
- db 0EAh,0,0,0,0 ;jmp far immediate
- ENDM
-
- ;***********************************************************************
- ;int 27 handling stubs
- ;code counts on exact byte sequence of each stub
- st27siz equ 8 ;number of bytes in int 27 stub
- st27max equ 32 ;maximum times we can grab int 27
- st27idx dw offset stb27 ;offset of current stub in use
- st27lim dw offset stb27+st27siz*(st27max-1) ;last usable stub
-
- stb27 label byte
- REPT st27max
- assume ds:nothing
- call int27work
- db 0EAh,0,0,0,0 ;jmp far immediate
- ENDM
-
- ;***********************************************************************
- ;put the interrupt address in es:bx into stub at di
- setstb proc near
- mov cs:[di+4],bx
- mov cs:[di+6],es
- ret
- setstb endp
-
- ;***********************************************************************
- ;clear the call to int2?work in stub at di
- clrstb proc near
- mov word ptr cs:[di],9090H
- mov byte ptr cs:[di+2],90H
- ret
- clrstb endp
-
- ;***********************************************************************
- ;do the real work of our int21 handler
- ;(control transferred from int 21 stub)
- ;note: if we run out of stub space, WATCH effectively disables itself
- int21work proc near
- assume ds:nothing
- pushf ;save flags
-
- ;check to see whether another program has grabbed int 21 or 27
- push ax
- push es
-
- xor ax,ax
- mov es,ax
- mov ax,ourcs
- cmp es:[4*21H+2],ax ;do we own int 21?
- jnz grab ;if not, grab it back
- cmp es:[4*27H+2],ax ;do we own int 27?
- jz haveem ;we're done if so
-
- ;we need to grab at least one interrupt
- grab: push bx
- push dx
- push di
- push ds
-
- push cs
- pop ds
- assume ds:cseg
-
- mov ax,es:[4*21H+2] ;get current int 21 segment
- cmp ax,ourcs ;do we own int 21?
- je have21 ;jump if so
- mov bx,es:[4*21H] ;get current int 21 offset
- mov es,ax ;es:bx = current int 21
- mov di,st21idx
- call clrstb ;turn existing stub into straight jump
- cmp di,st21lim ;room for more stubs?
- jae have21 ;forget it if no more room
- add di,st21siz ;move to next stub
- mov st21idx,di
- call setstb ;have next stub jump to current int 21
- mov dx,di
- mov ax,2521H
- pushf
- call dos_int
-
- have21: xor ax,ax
- mov es,ax
- mov ax,es:[4*27H+2] ;get current int 27 segment
- cmp ax,ourcs ;do we own int 27?
- je have27 ;jump if so
- mov bx,es:[4*27H] ;get current int 27 offset
- mov es,ax ;es:bx = current int 27
- mov di,st27idx
- call clrstb ;turn existing stub into straight jump
- cmp di,st27lim ;room for more stubs?
- jae have27 ;forget it if no more room
- add di,st27siz ;move to next stub
- mov st27idx,di
- call setstb ;have next stub jump to current int 27
- mov dx,di
- mov ax,2527H
- pushf
- call dos_int
-
- have27: pop ds
- assume ds:nothing
- pop di
- pop dx
- pop bx
-
- haveem: pop es
- pop ax
-
- ;trap DOS functions 31 and 49
- cmp ah,31H ;terminate and stay resident call?
- jne chk49
- call checkvec ;call routine to handle stayres calls
- jmp short ex21
-
- chk49: cmp ah,49H ;deallocate memory call?
- jne ex21
- call dealloc ;call routine to handle program unloading
-
- ex21: popf
- ret
- int21work endp
-
- ;***********************************************************************
- ;do the real work of our int27 handler
- ;(control transferred from int 27 stub)
- int27work proc near
- assume ds:nothing
- pushf
- push dx
- add dx,15 ;pass size of block in paras to checkvec
- shr dx,1
- shr dx,1
- shr dx,1
- shr dx,1
- call checkvec
- pop dx
- popf
- ret
- int27work endp
-
- ;***********************************************************************
- ;procedure dealloc
- ; checks whether deallocated memory is a PSP we're tracking
- ; if so, deletes that PSP block from our change table
- ; stores a new vector buffer
- dealloc proc near
- assume ds:nothing
- call setup
- mov bx,es ;save segment being deallocated in bx
- call pspmatch ;return si=0 if bx not a psp in changetable
- cmp si,0
- je dedone
- call pspremove ;remove found psp from changetable
- mov di,currvectors ;save the new version of the vector table
- call savevec
- dedone: call shutdown
- ret
- dealloc endp
-
- ;***********************************************************************
- ;procedure checkvec
- ; compares vectors to previous installation
- ; stores a new vector buffer
- ; on entry dx=paras to keep
- ; on exit dx=top segment going resident
- checkvec proc near
- assume ds:nothing
- call setup
- mov ah,51H ;get current PSP in bx
- pushf
- call dos_int
- add dx,bx ;dx = segment beyond that going resident
- call vechdr ;store the PSP segment of the program going resident
- call cmpvec ;scan the vector table looking for changes from our buffer
- mov di,currvectors ;save the new version of the vector table
- call savevec
- call shutdown
- ret
- checkvec endp
-
- ;***********************************************************************
- ;setup routine for checkvec and dealloc
- ; switches stacks
- ; saves registers
- ; sets ds=cs
- setup proc near
- pop cs:tmpret ;save return address as we switch stacks
-
- mov oldss,ss ;save current stack
- mov oldsp,sp
-
- cli ;switch to our stack
- mov ss,newss
- mov sp,newsp
- sti
-
- push ax ;store registers
- push bx
- push cx
- push dx
- push si
- push di
- push ds
- push es
-
- mov ax,cs
- mov ds,ax ;ds = cs
-
- push cs:tmpret
- ret
- setup endp
-
- ;***********************************************************************
- ;shutdown routine for checkvec and dealloc
- ; saves current vector image
- ; restores registers
- ; switches stacks
- shutdown proc near
- pop cs:tmpret
-
- pop es ;restore registers
- pop ds
- pop di
- pop si
- pop dx
- pop cx
- pop bx
- pop ax
-
- cli ;restore stack
- mov ss,cs:oldss
- mov sp,cs:oldsp
- sti
-
- push cs:tmpret
- ret
- shutdown endp
-
- ;***********************************************************************
- ;procedure pspmatch
- ; returns si pointing to start of psp rec if bx is found, else si=0
- ; entry: bx=PSP to match
- pspmatch proc near
- assume ds:cseg
- mov si,offset changevectors ;index into changevectors array
- mov dx,si
- add dx,nextchange ;dx = next available spot in changevectors
- matloop:cmp si,dx ;end of table?
- jae matdone
- cmp word ptr [si],pspid ;psp indicator?
- jnz matnext
- cmp [si+2],bx ;matching psp?
- jnz matnext
- ret ;return matching si
- matnext:add si,vrecsize
- jmp matloop
-
- matdone:xor si,si ;return si=0
- ret
- pspmatch endp
-
- ;***********************************************************************
- ;procedure pspremove
- ;removes psp started at index si
- pspremove proc near
- assume ds:cseg
- mov di,si ;save destination
- add si,vrecsize ;move to next record
- mov dx,offset changevectors
- add dx,nextchange ;dx = address of next available
- remloop:cmp si,dx ;end of table?
- jae remend
- cmp word ptr [si],pspid ;psp indicator?
- je remend
- add si,vrecsize
- jmp remloop
-
- remend: mov cx,dx
- sub cx,si ;cx = bytes to move
- shr cx,1 ;cx = words to move
- push ds
- pop es ;assure es=ds=cs
- cld
- rep movsw
- sub si,di ;update nextchange
- sub nextchange,si
- ret
- pspremove endp
-
- ;**************************************************************************
- ;procedure vechdr
- ; writes a header to the vector data area for this new TSR
- ; on entry bx has PSP of the new TSR, dx has top segment of TSR
- ; trashes di
- vechdr proc near
- assume ds:cseg
- cmp nextchange,vsize-vrecsize ;assure room for next record
- ja vecex ;ignore if no room
- mov di,nextchange ;index into changevectors array
- mov word ptr [di+changevectors],pspid ;store id word
- mov word ptr [di+changevectors+2],bx ;store PSP value
- ;two words in record left unitialized
- add nextchange,vrecsize ;move to next data element
- vecex: ret
- vechdr endp
-
- ;**************************************************************************
- ;procedure wrchg
- ; writes information about changed vectors to the data area
- ; on entry:
- ; cx has changed vector number
- ; ax:bp contains vector value
- ; on exit:
- ; flags changed
- wrchg proc near
- assume ds:nothing
- cmp nextchange,vsize-vrecsize ;assure room for next record
- ja wrcex
- push di
- mov di,offset changevectors
- add di,nextchange ;index into changevectors array
- mov cs:[di],cx ;store interrupt vector number
- mov cs:[di+2],bp ;store vector offset
- mov cs:[di+4],ax ;store segment
- ;one word in record left unused
- add nextchange,vrecsize ;move to next data element
- pop di
- wrcex: ret
- wrchg endp
-
- ;**************************************************************************
- ;procedure cmpvec
- ; compares vectors in buffer to those in use
- ; writes numbers of those different to data area
- ; doesn't write those that point outside of the TSR
- ; on entry:
- ; bx has base of TSR, dx has top of TSR
- ; on exit:
- ; ax,cx,si,di destroyed
- ; flags changed
- cmpvec proc near
- assume ds:nothing
- push bp
- push ds
- push es
-
- xor si,si ;source offset 0
- mov ds,si ;source address segment 0
- mov ax,cs
- mov es,ax
- xor cx,cx ;vector counter
- mov di,currvectors ;destination offset
- cld ;upward direction
-
- nexvec: cmpsw ;compare offsets
- je cmpseg ;compare segments if offsets equal
- cmpsw ;compare next word, ignore result
- jmp short cmprng ;make sure vector points into program
- cmpseg: cmpsw ;compare segments
- je vecinc ;jump if equal
- cmprng: mov bp,ds:[si-4] ;save vector offset in bp
- mov ax,ds:[si-2] ;save vector segment in ax
- cmp ax,bx ;lower than base of TSR?
- jb cmp21 ;jump if so
- cmprng2:cmp ax,dx ;above top of TSR?
- jae cmp21 ;jump if so
- call wrchg ;write changed vector
- jmp short vecinc
- cmp21: cmp cl,21H ;checking int 21?
- jne vecinc ;jump if not
- cmp ax,ourcs ;does int21 point to us?
- jne vecinc ;jump if not
- push di
- mov di,st21idx
- mov bp,cs:[di+4] ;save current offset in bp
- mov ax,cs:[di+6] ;save current segment in ax
- pop di
- cmp ax,bx ;lower than base of TSR?
- jb vecinc ;jump if so
- cmp ax,dx ;above top of TSR?
- jae vecinc ;jump if so
- call wrchg ;write changed vector
-
- vecinc: inc cx ;next vector number
- cmp cx,00FFH
- jbe nexvec ;continue until 256 vectors checked
-
- pop es
- pop ds
- pop bp
- ret
- cmpvec endp
-
- ;**************************************************************************
- ;procedure savevec
- ; saves image of interrupt vectors
- ; on entry:
- ; di has destination offset
- ; on exit:
- ; ax,cx,si,di destroyed
- ; flags changed
- savevec proc near
- assume ds:nothing
- push ds
- push es
- xor si,si ;offset 0
- mov ds,si ;source address segment 0
- mov ax,cs
- mov es,ax ;destination always in this code segment
- mov cx,200H ;512 integers to store
- cld ;copy up
- rep movsw ;copy vectors to our table
- pop es
- pop ds
- ret
- savevec endp ;of proc savevec
-
- ;**************************************************************************
- ;resident portion above, temporary portion below
- ;**************************************************************************
-
- align 16
- bmesg db 'Cannot install WATCH more than once....',13,10,36
- mesg db 'WATCH 3.0, Copyright 1991 TurboPower Software',13,10
- mesg2 db 'Installed successfully',13,10,36
- pname db 'TSR WATCHER'
- plen equ $-pname ;length of string
-
- ;**************************************************************************
- init proc near
- assume ds:cseg
-
- ;use int 16h test to check for previous installation
- mov ax,getid ;int16h diagnostic request
- int 16h ;now, ax=chkid if installed
- cmp ax,chkid ;TSR already installed?
- jne success ;no - jump if not installed
-
- ;error exit
- mov dx,offset bmesg ;error message
- mov ah,09H
- int 21H ;DOS print string
- mov ax,4C01H ;exit with error
- int 21H
-
- ;print a success message
- success: mov dx,offset mesg ;start of message to write
- mov ah,09H
- int 21H ;DOS print string
-
- ;relocate ourselves out of the way of the vector tables
- mov ax,cs
- mov es,ax
- mov di,newloc+10H
- push di ;will act as a return address
- mov si,offset newstk
- mov cx,lastcode-newstk
- rep movsb ;move code
- ret ;"return" to the relocated code
-
- ;initialize location of WATCH stack
- newstk: mov newsp,newstackpos+ssize
- mov newss,cs ;stack seg is code seg
-
- ;get int 16H vector
- mov ax,3516H ;GetVector DOS function call
- int 21H
- mov old16,bx ;store first word of old21
- mov old16[2],es ;store second word
-
- ;get int 27H vector
- mov ax,3527H ;GetVector DOS function call
- int 21H
- mov ax,offset setstb
- mov di,st27idx
- call ax ;save vector in first stub
-
- ;get int 21H vector
- mov ax,3521H ;GetVector DOS function call
- int 21H
- mov old21,bx ;store first word of old21 (offset)
- mov old21[2],es ;store second word (segment)
- mov ax,offset setstb
- mov di,st21idx
- call ax ;save vector in first stub
-
- ;put an id label at offset 80H to allow other programs to recognize WATCH
- mov ax,cs
- mov es,ax
- mov cx,plen ;length of name string
- mov si,offset pname ;offset of name string
- mov di,offset cmdline ;offset of DOS command line
- cld ;transfer in forward direction
- mov al,cl
- stosb ;store length byte first
- rep movsb ;transfer characters
-
- ;store image of original vector table (overwrites messages)
- mov di,origvectors
- mov ax,offset savevec
- call ax ;absolute call works as code is moved
-
- ;store it again into the current vector table
- mov di,currvectors
- mov ax,offset savevec
- call ax ;absolute call works as code is moved
-
- ;install the new vectors
- mov ax,2516H
- mov dx,offset newint16
- int 21H
-
- mov ax,2527H
- mov dx,offset stb27
- int 21H
-
- mov ax,2521H
- mov dx,offset stb21
- int 21H
-
- ;save cs in a convenient place
- mov ourcs,cs
-
- ;terminate and stay resident
- mov dx,newloc
- add dx,000FH
- mov cl,4
- shr dx,cl
- mov ax,3100H ;return success code
- pushf
- call dos_int ;don't log vectors WATCH itself takes over
- lastcode:
- init endp
-
- Cseg ends
- end ComEntry