home *** CD-ROM | disk | FTP | other *** search
- ;MOUSER.007 - MOUSE cursoR for the Microsoft Mouse & Compatibles - 09/87
- ; --------------------------------------------------------------------------
- ; (c) OZZARD of WIS / Paul Noeldner, 510 S. Dickinson, Madison, WI 53703
- ; This Software is In the Public Domaine
- ; OZZARD of WIS assumes no liability for any loss or damage from use of this
- ; program. Use of the program constitutes agreement to this disclaimer.
- ; When copied or distributed, it must include this ASM code documentation.
- ; --------------------------------------------------------------------------
- ; PURPOSE
- ; MOUSER is dedicated to all cats (cursor arrow tappers) out there who are
- ; interested in seeing how nice a mouse can work in everyday PC programs.
- ; The feel of high-powered point-and-click mouse software, can be quickly
- ; realized in any scrolling-menu program by using MOUSER and a mouse -
- ; without high-falutin graphics or window software, or gobs of TSR memory.
- ; --------------------------------------------------------------------------
- ; ENVIRONMENT
- ; The MicroSoft(Tm) MOUSE.COM or MOUSE.SYS mouse driver, or a compatible
- ; using the same driver protocol, must be implemented to run MOUSER.
- ; MOUSER then works with ANY PROGRAM that accepts cursor up/down/left/right.
- ; The mouse buttons can be used for COMMON KEYS like return and escape -
- ; both mouse speed, and buttons, can be set via parms to suit your needs.
- ; --------------------------------------------------------------------------
- ; USE
- ; The MOUSER defaults - average cursor speed, and RETURN/ESCAPE/BREAK buttons,
- ; work well in many applications. Individuals may wish to adjust the
- ; speed and the button functions for particular applications, to make mouse
- ; use satisfying and productive (rather than tedius or target practice).
- ; The cursor speed and buttons can be customized by you to complement
- ; your applications. You run MOUSER with control parameters from the DOS
- ; prompt or in any application .bat procedure file.
- ; --------------------------------------------------------------------------
- ; PARMS
- ; MOUSER Hn Vn Lnn Rnn Bnn?
- ; ? - help - which also appears if parms are not understood
- ; Hn, Vn n=1 to 9 - sets Horizontal or Vertical cursor speed
- ; Lx, Rx, Bx - x=character or 2-digit ASCII value - sets Left,
- ; Right, or Both (pressed together) button key values
- ; Digit values above 31 are treated as 'extended' keys.
- ; These parms are all optional, in any order, with any delimiters.
- ; --------------------------------------------------------------------------
- ; SAMPLES
- ; MOUSER ? - shows full help, sample button ASCII values.
- ; MOUSER - sets default medium cursor, RETURN, ESCAPE buttons
- ; MOUSER H1 V1 L27 R13 B/ - slow cursor, left ESCAPE, right RETURN, both /
- ; This might be appropriate for a scrolling-bar menu program.
- ; This example shows how to reverse the return/escape buttons,
- ; if you happen to prefer them in that order. Both buttons would
- ; input a slash, which may be useful for spreadsheet commands.
- ; MOUSER V9 L73 R81 B27 - fast vertical, left PGUP, right PGDN, both ESC
- ; This would be useful in a text file browse, and to
- ; quickly position the cursor and mark blocks in an editor.
- ; The button keys work in any program that accepts the specified keys.
- ; The MOUSER ? help display shows several more common key values.
- ; See your DOS or BASIC manual for a complete list of the ASCII values
- ; of keys below 32 (space), such as 13-RETURN, and the 'extended' keys
- ; such as 81-PGUP. Any values over 32 are considered 'extended' keys.
- ; If a character is specified instead of a 2-digit value, it is used.
- ; MOUSER + - the + parm is the currently implemented means to
- ; reactivate MOUSER if it becomes deactivated.
- ; Once you use +, it must be used subsequently.
- ; Hopefully, the next version will not need this.
- ; --------------------------------------------------------------------------
- ; The regular cursor keys continue to work as usual. Programs that have
- ; their own mouse driver support, work independently of MOUSER.
- ; MOUSER does not prevent or preclude any normal use of the keyboard.
- ; --------------------------------------------------------------------------
- ; Some programs appear to disable MOUSER; you may want to put MOUSER
- ; in the application .bat startup file, after the application program,
- ; to turn the mouse back on after running the application. Programs
- ; that have custom mouse drivers are commonly guilty of this crime.
- ; In that case, use the + parameter to ask that a fresh copy be loaded.
- ; Once the + parameter is used, it must subsequently be used each time.
- ; --------------------------------------------------------------------------
- ; MORE ABOUT TSR AND RELOADING
- ; Normally one copy of MOUSER loads memory resident; after that, the parms
- ; are updated whenever the program is run. The program takes about 600 bytes
- ; of memory - much less than 'custom' mouse menus. By not reloading
- ; each time it is run, it saves that much more memory for you.
- ; If the mouse driver has been disengaged by any program, it is reengaged
- ; by using the + parameter, which loads a fresh copy of MOUSER. A future
- ; version of this program should get around that requirement, but my
- ; knowledge of assembler is pretty weak and I cannot seem to reengage by
- ; pointing at the current resident version. Give it a hack - give me a call!
- ; See the code related to tsrsav and address 126h - that was my attempt.
- ; --------------------------------------------------------------------------
- ; ACKNOWLEDGMENT
- ; The program code was modeled after MOUSEKEY by Jeff Prosise / Ziff Davis.
- ; --------------------------------------------------------------------------
- ; CHANGES FROM MOUSEKEY
- ; While MOUSER can be used in place of MOUSEKEY, the defaults are different.
- ; Enhancements have been made to improve user control over parameters.
- ; The program normally loads just one TSR copy even if run more than once.
- ; --------------------------------------------------------------------------
- ; SPECIFIC IMPROVEMENTS
- ; (1) Added control over sensitivity of horizontal motion.
- ; (2) Prioritized vertical above horizontal movement (otherwise the mouse
- ; tends to jump left and right while positioning vertically).
- ; (3) Set defaults to suit menu scrolling - slower cursor speed, and
- ; mouse buttons set to RETURN, ESCAPE (instead of MOUSEKEY PGUP, PGDN).
- ; (4) Allow optional parms for speed 1-9 and custom mouse button values
- ; specified as actual characters or 2-digit ASCII codes.
- ; Example: MOUSER H5 V5 L13 R27 B03 (example indicates the defaults).
- ; All parms are optional in any order. Any delimiters are ignored.
- ; Any unrecognized 'junk' on the command line displays help and a message.
- ; (5) Added processing for 'both buttons' pressed, giving a third key value
- ; in addition to left and right button values. Default is 03, CTRL-C.
- ; (5) Added help - enter MOUSER ? for help display.
- ; (6) Posts current TSR version if already loaded, by finding itself in
- ; memory. This is especially important since the intent is to run
- ; MOUSER whenever it is desirable to set parms to suit particular programs.
- ; It may be run as part of .BAT files for specific applications.
- ; Currently, if driver is 'disengaged', must reload using + parm.
- ; --------------------------------------------------------------------------
- ; PROGRAM STRUCTURE
- ; The following program structure is based on Jeff Prosise's MOUSEKEY.
- ; It includes a TSR segment and an initialization segment that now sets the
- ; parameters and terminates after pointing the PLP to the end of the TSR part.
- ; If already loaded, parms are posted to the current address of the program.
- ; --------------------------------------------------------------------------
- bios_data segment at 40h
- org 1Ah
- buffer_head dw ? ;pointer to keyboard buffer head
- buffer_tail dw ? ;pointer to keyboard buffer tail
- org 80h
- buffer_start dw ? ;starting keyboard buffer address
- buffer_end dw ? ;ending keyboard buffer address
- bios_data ends
- ;
- code segment para public 'code'
- assume cs:code
- org 100h
- begin: jmp init ;goto initialization code
- ; --------------------------------------------------------------------------
- ;This part was enhanced in MOUSER to include hdelay and lkey/rkey/bkey values,
- ;and to support location and posting of current TSR version of program.
- ; --------------------------------------------------------------------------
- resfinder db 'MOUSER CODE' ;This is used to find and change parms
- ;if MOUSER program is already resident.
- ;Address of above literal is mcb+113h.
- ;If this db block is changed, also
- ;change the initialize mcb: and post:
- ;code that finds and changes the parms.
- ;The following parms are at mcb+11Eh.
- vdelay db 5 ;vertical delay (set by Vn speed parm)
- hdelay db 5 ;horizontal delay (set by Hn parm)
- lkey dw 000Dh ;keycode for left button (set by Lnn)
- rkey dw 001Bh ;keycode for right button (set by Rnn)
- bkey dw 0003h ;keycode for both buttons (set by Bnn)
- tsrsav dw 0000h ;address of 'mouse' segment below
- ;
- vcount db 1 ;vertical mouse mickey counter
- hcount db 1 ;horizontal mouse mickey counter
- vflag dw ? ;vertical count sign flag
- hflag dw ? ;horizontal count sign flag
- keycode db 4Dh,4Bh,50h,48h ;keycodes for up/dn/lf/rt cursor keys
- ;------------------------------------------------------------------------------
- ;This subroutine is handed control by the mouse driver when the mouse is
- ;moved or a button is pressed.
- ;------------------------------------------------------------------------------
- mouse proc far
- ;
- ;Determine which event occurred and branch accordingly.
- ;
- test ax,2 ;was the left button pressed?
- jnz lbut ;yes, then branch
- test ax,8 ;was the right button pressed?
- jnz rbut ;yes, then branch
- ; --------------------------------------------------------------------------
- ;Move the cursor in the direction indicated by the most recent mouse move.
- ;This was modified from MOUSEKEY to prioritize vertical over horizontal,
- ;and to test a horizontal delay factor.
- ; --------------------------------------------------------------------------
- mouse0: mov ax,11 ;function 11
- int 51 ;read mouse motion counters
- mov hflag,0 ;initialize sign flags
- mov vflag,2
- xor al,al ;zero AL for extended keycode
- cmp dx,0 ;vertical count positive?
- jge mouse1 ;yes, then branch
- inc vflag ;record negative condition
- neg dx ;convert negative to positive
- mouse1: cmp cx,0 ;horizontal count positive?
- jge mouse2 ;yes, then branch
- inc hflag ;record negative condition
- neg cx ;convert negative to positive
- mouse2: mov bx,vflag ;assume motion was vertical
- cmp dx,cx ;was the assumption correct?
- jae mouse4 ;yes, then branch
- mov bx,hflag ;no, then correct it
- dec hcount ;decrement horizontal count
- jz mouse3 ;continue if count is zero
- ret ;exit if it's not
- ; --------------------------------------------------------------------------
- ;The hdelay/vdelay values allow control over horizontal sensitivity.
- ;These are input as Hn Vn parms as speed 1-slow to 9-fast, and converted
- ;for decrementing to delay 9-slow to 1-fast. The delay simply ignores
- ;the indicated number of mickeys (mouse increments) before responding.
- ;They correspond roughly to screen pixels; e.g. speed 1 moves 1 pixel where
- ;speed 9 moves 9 pixels in a similar physical mouse movement (about 1/32").
- ; --------------------------------------------------------------------------
- mouse3: mov ah,hdelay
- mov hcount,ah ;reset horizontal delay
- jmp setkey ;
- mouse4: dec vcount ;decrement vertical delay
- jz mouse5 ;continue if count is zero
- ret ;exit if it's not
- mouse5: mov ah,vdelay
- mov vcount,ah ;reset vertical delay
- setkey: mov ah,keycode[bx] ;get keycode from table
- jmp insert ;insert it into keyboard buffer
- ;
- ;The left button was pressed. Load AX with the keycode.
- ;
- lbut: test ax,8
- jnz bbut ;both buttons?
- mov ax,lkey ;load left button keycode
- jmp insert ;insert into the keyboard buffer
- ;
- ;The right button was pressed. Load AX with the keycode.
- ;
- rbut: mov ax,rkey ;load keycode
- jmp insert ;insert into keyboard buffer
- ;
- ;Both buttons were pressed. Load AX with the keycode.
- ;
- bbut: mov ax,bkey ;load both button keycode
- ;
- ;Insert the keycode in AX into the keyboard buffer.
- ;
- insert: mov bx,bios_data ;point DS to BIOS data area
- mov ds,bx
- assume ds:bios_data
- cli ;disable interrupts
- mov bx,buffer_tail ;get buffer tail address
- mov dx,bx ;transfer it to DX
- add dx,2 ;calculate next buffer position
- cmp dx,buffer_end ;did we overshoot the end?
- jne insert1 ;no, then continue
- mov dx,buffer_start ;yes, then wrap around
- insert1: cmp dx,buffer_head ;is the buffer full?
- je insert2 ;yes, then end now
- mov [bx],ax ;insert the keycode
- mov bx,dx ;advance the tail
- mov buffer_tail,bx ;record its new position
- insert2: sti ;enable interrupts
- assume ds:nothing
- ret ;exit user-defined subroutine
- mouse endp
- ;
- ;------------------------------------------------------------------------------
- ;INIT routine points the mouse driver to the user-defined subroutine,
- ;then leaves it resident in memory.
- ;------------------------------------------------------------------------------
- init proc near
- jmp setup
- ;
- logo db 201,205,205,181
- db' MOUSER.007 / 10/87 / OZZARD of WIS / Public Domain / ?-HELP '
- db 198,205,205,187,13,10,'$'
- ;
- helpmsg db 186
- db ' Paul Noeldner, Madison, WI 608-255-5577 '
- db 186,13,10,186
- db ' ',15,' For CATS (Cursor Arrow Tappers) with MS(tm) compatible Mice. '
- db 186,13,10,186
- db ' ',15,' To use a mouse in any program that uses cursor arrows, just '
- db 186,13,10,186
- db ' set the speed for easy pointing and buttons for common keys. '
- db 186,13,10,186
- db ' ',15,' Put MOUSER into .BAT files, set for specific applications. '
- db 186,13,10,186
- db ' MOUSER H5 V5 L13 R27 B03 Example showing default parameters. '
- db 186,13,10,186
- db ' MOUSER H1 V2 B/ Slower cursor (for 123-style menus). '
- db 186,13,10,186
- db ' MOUSER V9 L73 R81 B27 Faster with PGUP/PGDN (for browsing). '
- db 186,13,10,186
- db ' Hn, Vn Horizontal, Vertical speed 1-9, default 5-medium. '
- db 186,13,10,186
- db ' Lx, Rx, Bx Sets button key characters or ASCII key codes. '
- db 186,13,10,186
- db ' + Loads new copy of MOUSER (use only if disengaged). '
- db 186,13,10,186
- db ' All parms are optional, in any order, with any delimiters. '
- db 186,13,10,186
- db ' Button ASCII key values over 31 are used for extended keys. '
- db 186,13,10,186
- db ' These are commonly used keys (see a BASIC manual for more): '
- db 186,13,10,186
- db ' 03 - CTRL/C 09 - TAB 13 - RETURN 27 - ESCAPE '
- db 186,13,10,186
- db ' 71 - HOME 73 - PGUP 79 - END 81 - PGDN '
- db 186,13,10,186
- db ' 82 - INSERT 83 - DELETE 59 THRU 68 - F1 THRU F10 '
- db 186,13,10,200
- db 67 dup ('═')
- db 188,13,10,'$'
- ;
- errmsg db 7,200
- db 8 dup ('═')
- db 16,' DRIVER MISSING: Install MOUSE.SYS or MOUSE.COM ',17
- db 9 dup ('═')
- db 188,7,13,10,'$'
- ;
- junkmsg db 7,200
- db 7 dup ('═')
- db 16,' UKNOWN INPUT PARAMETER - CHECK THIS HELP DISPLAY ',17
- db 8 dup ('═')
- db 188,7,'$'
- ;
- loadmsg db 200
- db 18 dup ('═')
- db 16,' OK - Mouse Cursor Installed ',17
- db 18 dup ('═')
- db 188,13,10,'$'
- ;
- postmsg db 200
- db 16 dup ('═')
- db 16,' OK - Mouse Cursor Parms Adjusted ',17
- db 15 dup ('═')
- db 188,13,10,'$'
- ;
- endparm dw 81h ;end of parm input
- mcbptr dw 0000h ;pointer to memory control blocks
- found db 'N' ;is MOUSER already loaded TSR in memory
- newcopy db 'N' ;indicates if + (update) parm entered
- lit db ? ;literal parm input character
- dig db 'N' ;found a digit?
- ;
- ;Logo display
- ;
- setup: lea dx,logo ;show logo
- mov ah,9
- int 21h
- call parms ;process input parms
- call mcbwalk ;check if MOUSER is already resident
- endit: jmp allthru ;exit program
- ;
- init endp
- ;
- ;-----------------------------------------------------------------------------
- ;Process the command line parms (if any)
- ;
- parms proc near
- mov bx,0 ;point at input parm length in Pgm Seg Prefix
- mov si,80h
- mov ah,0
- mov al,byte ptr[si] ;now we have the length
- add ax,80h ;compute end of parm
- mov endparm,ax ;remember it
- inc si ;skip initial space in input parm
- ;
- parmloop:
- mov bx,0
- inc si ;get input from command parm
- cmp si,endparm ;see if at end of parm
- jle parse ;if not, process it
- ret ;if so, done with setup work
- ;
- parse: mov al,byte ptr[si] ;get next character
- cmp al,' ' ;skip blanks
- je parmloop
- cmp al,'/' ;skip slashes
- je parmloop
- cmp al,',' ;skip commas
- je parmloop
- cmp al,'+' ;load new copy?
- jne help
- mov newcopy,'Y'
- jmp parmloop
- help: cmp al,'?' ;show help?
- jne case
- lea dx,helpmsg ;help display
- mov ah,9
- int 21h
- int 20h
- ;
- case: cmp al,91 ;upper case?
- jl upper
- sub al,32 ;convert lower to upper case
- ;
- upper: call parmcheck ;see if H, V, L, R
- jmp parmloop ;continue parsing thru parm
- ;
- parms endp
- ;
- ;-----------------------------------------------------------------------------
- ;Check for Horizontal and Vertical Speed, Left/Right/Both button control values
- ;
- parmcheck proc near
- cmp al,'H' ;is it horizontal speed parm
- jne parmv ;if not, check vertical speed
- call digedit ;check it out, value returned in al
- cmp dig,'Y' ;is it a digit?
- jne junk ;if not, return message
- not al ;invert 10-speed to get delay
- mov hdelay,al ;store horizontal delay value
- ret ;back to parsing parms
- ;
- parmv: cmp al,'V' ;is it vertical speed parm?
- jne parml ;if not, check left button
- call digedit ;check it out, value returned in al
- cmp dig,'Y' ;is it a digit?
- jne junk ;if not, return message
- not al ;invert 10-speed to get delay
- mov vdelay,al ;store vertical delay value
- ret
- ;
- parml: cmp al,'L' ;is it left button parm?
- jne parmr ;if not, check right button
- call dighex ;get digits into hex
- mov lkey,ax ;set left button key code
- ret
- ;
- parmr: cmp al,'R' ;is it right button parm?
- jne parmb ;if not,check both buttons
- call dighex ;get digits into hex
- mov rkey,ax ;set right button key code
- ret
- ;
- parmb: cmp al,'B' ;is it both buttons parm?
- jne junk ;send message if unknown parm
- call dighex ;get digits into hex
- mov bkey,ax ;set both buttons key code
- ret
- ;
- ;Junk parm error message
- ;
- junk: lea dx,helpmsg ;help, plus error message for invalid parms
- mov ah,9
- int 21h
- lea dx,junkmsg
- mov ah,9
- int 21h
- int 20h ;and program ends
- ;
- parmcheck endp
- ;
- ;-----------------------------------------------------------------------------
- ;Digits to hex routine
- ;
- dighex proc near
- call digedit ;get next digit
- cmp dig,'Y' ;is it a digit?
- je digcon ;if so, continue
- ret ;otherwise got literal, return it
- digcon: cbw ;byte in al goes to word in ax
- xchg ax,bx ;trade digit and number
- mov cx,10d
- mul cx ;number in ax times 10
- xchg ax,bx ;trade number and digit
- add bx,ax ;add digit to number
- call digedit ;get next digit
- cmp dig,'Y' ;is it a digit?
- jne junk ;return message if not
- cbw ;byte in al goes to word in ax
- xchg ax,bx ;trade digit and number
- mov cx,10d
- mul cx ;number in ax times 10
- xchg ax,bx ;trade number and digit
- add bx,ax ;add digit to number
- mov ax,bx
- cmp al,20h ;is number > 20?
- jl setok ;no, set as is
- mov ah,al ;yes, make it high byte
- mov al,0 ;null low byte
- setok: ret ;all thru, got 2 digits into binary form
- ;
- dighex endp
- ;
- ;-----------------------------------------------------------------------------
- ;Get value of ASCII digit or literal, return in ah
- ;
- digedit proc near
- mov dig,'N' ;may not have a digit here
- inc si
- mov al,byte ptr[si] ;get next byte
- mov lit,al ;save literal value
- sub al,30h ;drop ascii code to convert digit to value
- jl liter ;if not digit, use literal
- cmp al,9d ;
- jg liter ;if not digit, use literal
- sub al,11d
- mov dig,'Y' ;yes, got a digit
- ret
- liter: or ax,ax ;get ax to null
- mov al,lit ;plug in literal character
- ret ;back to parm scan
- ;
- digedit endp
- ;
- ;-----------------------------------------------------------------------------
- ;See if MOUSER is already resident by walking memory control blocks.
- ;
- ;Each MCB is marked with M in first byte, last block has Z in first byte.
- ;The length of each MCB is in byte 3. Adding len + 1 locates the next MCB.
- ;If MOUSER is already resident, parms are updated in that copy of the program.
- ;
- mcbwalk proc near
- push bp ;remember right where we were (we hope)
- push ax ;the stack was getting messed in this code
- push bx
- push cx
- push dx
- push ds
- push es
- mov ah,52h ;DOS fn to get first memory control block
- int 21h
- mov ax,es:[bx-2] ;stash starting mcb address in variable
- mov mcbptr,ax
- ;
- search: mov es,mcbptr ;get first byte at current mcb address
- mov dl,byte ptr es:[0]
- cmp dl,'M' ;an M means TSR, but not last one loaded
- je gotmcb
- pop es
- pop ds
- pop dx
- pop cx
- pop bx
- pop ax
- pop bp ;back to current memory values and pointers
- ret ;Done with TSR chain
- ;
- gotmcb: cmp found,'Y' ;see if already found
- je nextmcb ;skip to end of chain if already found
- mov dl,byte ptr es:[113h] ;if not found yet, look for 'MOUSER CODE'
- cmp dl,'M' ;literal starting in byte 4
- jne nextmcb
- mov dl,byte ptr es:[114h]
- cmp dl,'O'
- jne nextmcb
- mov dl,byte ptr es:[115h]
- cmp dl,'U'
- jne nextmcb
- mov dl,byte ptr es:[116h]
- cmp dl,'S'
- jne nextmcb
- mov dl,byte ptr es:[117h]
- cmp dl,'E'
- jne nextmcb
- mov dl,byte ptr es:[118h]
- cmp dl,'R'
- jne nextmcb
- mov dl,byte ptr es:[11Ah]
- cmp dl,'C'
- jne nextmcb
- mov dl,byte ptr es:[11Bh]
- cmp dl,'O'
- jne nextmcb
- mov dl,byte ptr es:[11Ch]
- cmp dl,'D'
- jne nextmcb
- mov dl,byte ptr es:[11Dh]
- cmp dl,'E'
- jne nextmcb
- call post ;post parms to existing MOUSER TSR copy
- jmp nextmcb
- ;
- nextmcb: mov ax,mcbptr ;on to the next mcb
- mov es,ax
- add ax,word ptr es:3 ;length of block is in byte 3
- inc ax ;add length plus 1 for next mcbptr
- mov mcbptr,ax
- jmp search
- ;
- mcbwalk endp
- ;
- ;-----------------------------------------------------------------------------
- ;Post parms to data locations in current resident version of MOUSER
- ;
- post proc near
- mov found,'Y' ;indicate TSR now found
- mov al,vdelay ;and post V, H, L, R and B parms to memory
- mov byte ptr es:[11Eh],al
- mov al,hdelay
- mov byte ptr es:[11Fh],al
- mov ax,lkey
- mov word ptr es:[120h],ax
- mov ax,rkey
- mov word ptr es:[122h],ax
- mov ax,bkey
- mov word ptr es:[124h],ax
- ;
- ;The following code should re-activate the mouse driver addressability
- ;to the currently loaded tsr mouse routine we just found.
- ;It is commented out because the code as written here leaves the mouse
- ;driver pointing into never-never land somewhere. Please help me Peter Pan!
- ;
- ; mov ax,12 ;function 12, set ms driver active
- ; mov cx,11 ;subroutine call mask
- ; mov dx,word ptr es:[126h] ;offset of tsrsav pointer to mouse seg
- ; int 51 ;pass information to mouse driver
- ret
- ;
- post endp
- ;
- ;-----------------------------------------------------------------------------
- ;If MOUSER already TSR, end normally, else end TSR
- ;
- allthru proc
- cmp found,'Y'
- jne tsr
- cmp newcopy,'Y'
- je tsr
- mov ah,9 ;send post message
- lea dx,postmsg
- int 21h
- int 20h ;normal exit to DOS
- ;
- tsr: call msmouse ;make sure mouse driver is resident
- mov ah,9 ;send load message
- lea dx,loadmsg
- int 21h
- mov ax,12 ;function 12, set ms driver active
- mov cx,11 ;subroutine call mask (bits 1011)
- ;call if mouse moved, or button tapped
- mov dx,offset mouse ;point ES:DX to the TSR subroutine
- mov tsrsav,dx ;and save this address for later use
- int 51 ;pass address to mouse driver
- lea dx,init ;point DX to end of resident code
- int 27h ;terminate-but-stay-resident
- ;
- allthru endp
- ;
- ;-----------------------------------------------------------------------------
- ;Make sure the ms mouse hardware and software are in place.
- ;
- msmouse proc near
- mov ax,0 ;function 0
- int 51 ;get installation flag
- or ax,ax ;is AX zero?
- jne msok ;proceed with loading
- mov ah,9 ;print error message and abort
- lea dx,errmsg
- int 21h
- int 20h
- ;
- msok: ret ;continue loading
- ;
- msmouse endp
- code ends
- end begin
-