home *** CD-ROM | disk | FTP | other *** search
- ;============================================================================
- ; Mouse interface for QuickBASIC V4.x, Microsoft BASIC 6.X, and the
- ; Microsoft BASIC Professional Development System 7.X.
- ;
- ; Written by Tony Elliott (CIS 76220,2575)
- ;
- ; For QBNews in March, 1991 and released into the Public Domain.
- ;
- ; Assemble using MASM 5.1
- ;===========================================================================
-
- .Model Medium, Basic
- .Code _MouseCode
-
- ; We store our variables in our code segment to keep them out of DGROUP.
-
- MouseButtons db 0 ;Our "initialized" flag
- PixelsOn db 0 ;If <> 0, return coordinates in pixels
- StateSegment dw 0 ;Memory segment where mouse state is stored
- SaveBytes dw 0 ;Number of bytes required to save state
- OnExitSet db 0 ;Indicates successful call to B_OnExit
-
- UEventActive db 0 ;-1 if our mouse event handler is active
- EventCause dw 0 ;The cause of the event
- ButtonState dw 0 ;When mouse event hits, button state,
- VertPos dw 0 ; vertical and horizontal locations stored
- HorizPos dw 0 ; here until fetched by programmer.
-
- Extrn B$SETM :Far ;BASIC's SETMEM routine
- Extrn SetUEvent :Far ;Sets a BASIC flag that triggers a UEVENT.
- Extrn B_OnExit :Far ;BASIC's routine to set procs to be called
- ; on program restart or termination.
- ;---------------------------------------------------------------------------
-
- MousePixelsOn proc
-
- ;Sets an internal flag which tells us to return mouse corrdinates in
- ;pixel format. The default is to return base 1 row/column coordinates
- ;like BASIC uses. Use the routine MousePixelsOff to reset the
- ;coordinate system back to row/columns.
-
- ;From BASIC:
- ;
- ; DECLARE SUB MousePixelsOn () 'This is optional
- ;
- ; CALL MousePixelsOn 'Or, when the declare is present,
- ; MousePixelsOn
-
- mov byte ptr cs:PixelsOn, -1 ;Turn the flag on
- ret ;That was easy, wasn't it?
-
- MousePixelsOn endp
-
- ;---------------------------------------------------------------------------
-
- MousePixelsOff proc
-
- ;Sets an internal flag which tells us to return mouse corrdinates in
- ;base 1 row/column format. This the default. You need to call this routine
- ;only if you have previously called the MousePixelsOn routine and you
- ;wish to return to row/column coordinates.
-
- ;From BASIC:
- ;
- ; DECLARE SUB MousePixelsOff () 'This is optional
- ;
- ; CALL MousePixelsOff 'Or, when the declare is present,
- ; MousePixelsOff
-
- mov byte ptr cs:PixelsOn,0 ;Set the flag to OFF.
- ret
-
- MousePixelsOff endp
-
- ;---------------------------------------------------------------------------
-
- MouseReset proc
-
- ; Initializes the mouse. The mouse driver is initialized to the
- ; following state:
- ;
- ; - Mouse pointer is at the center of the screen
- ; - Display page for mouse set to 0
- ; - Mouse pointer is hidden (off)
- ; - Mouse pointer shape is the default arrow shape in the graphics
- ; video modes or a reverse block in the text modes.
-
- ; From BASIC:
- ;
- ; DECLARE FUNCTION MouseReset% ()
- ;
- ; NumberOfButtons% = MouseReset%
- ; IF NumberOfButtons% THEN
- ; PRINT "Mouse with";NumberOfButtons%;"buttons is installed and reset."
- ; ELSE
- ; PRINT "Mouse not detected."
- ; END IF
-
- xor ax,ax ;Function 0
- int 33h ;Returns number of buttons in bx
- or bx,bx ;Is bx non-zero?
- jz @F ;No. Mouse not detected. Get out.
-
- mov cs:MouseButtons,bl ;Mouse was detected. Store # buttons.
-
- push cs ;Setup for call to B_OnExit. Push
- mov cx,offset MouseExit ; segment and offset of our clean-
- push cx ; up routine onto the stack.
- call B_OnExit ;Tell BASIC to stick it (in its table)
-
- mov al,cs:MouseButtons ;Move # of buttons into ax for return
- xor ah,ah ;Zero ah
-
- @@: ret ;Back to BASIC. Contents of AX is
- ;returned as function result.
- MouseReset endp
-
- ;-----------------------------------------------------------------------------
-
- MouseAlreadyReset proc
-
- ;Returns the number of button the mouse has -if- the driver has already
- ;been reset, otherwise it returns zero. This routine provides an easy
- ;method of determining if the mouse driver has already been reset by the
- ;current program.
-
- ;From BASIC:
- ;
- ;DECLARE FUNCTION MouseAlreadyReset% ()
- ;Buttons% = MouseAlreadyReset%
- ;IF Buttons% THEN
- ; PRINT "Mouse with";Buttons%;" buttons has already been reset!"
- ;ELSE
- ; PRINT "Mouse has not yet been reset."
- ;END IF
-
- xor ah,ah ;Zero AH
- mov al,cs:MouseButtons ;Number of buttons into al
- ret ;Returns AX as result of integer function
-
- MouseAlreadyReset endp
-
- ;-----------------------------------------------------------------------------
-
- MouseInstalled proc uses ds
-
- ;Check to see if a mouse is installed WITHOUT resetting it. The
- ;MouseReset function will still have to be invoked before the other
- ;mouse routines will function.
-
- ;From BASIC:
- ;
- ; DECLARE FUNCTION MouseInstalled% ()
- ;
- ; IF MouseInstalled% THEN
- ; PRINT "A mouse IS installed."
- ; ELSE
- ; PRINT "A mouse was not detected."
- ; END IF
-
- cmp cs:MouseButtons,0 ;Have we already initialized it?
- jz @F ;If not, continue the check.
-
- mov ax,-1 ;It has been reset so it must be
- jmp short ExitInstall ;installed. Set return to -1 (TRUE).
-
- @@:
- xor ax,ax ;Zero ax
- assume ds:nothing
- mov ds,ax ;Move that into ds referencing the IVT
- mov bx,ds:[0cch] ;Offset of Int 33h (mouse) into bx
- mov cx,ds:[0ceh] ;Segment of Int 33h into cx
- or cx,cx ;Is segment zero?
- jz ExitInstall ;If so, exit
- mov ds,cx ;Point ds to segment of Int 33h handler
- cmp byte ptr ds:[bx],0cfh ;Is the handler pointing to an IRET?
- jz ExitInstall ;If so, no mouse driver loaded. Exit.
- not ax ;If it's not an IRET then it must be
- ; a valid driver. Return -1 (TRUE).
- ExitInstall:
- ret ;Back to BASIC.
-
- MouseInstalled endp
-
- ;------------------------------------------------------------------------------
-
- MousePointerOn proc
-
- ;Displays the mouse pointer (cursor) and cancels any previous mouse
- ;exclusion area defined with the routine MouseSetExclusionArea.
-
- ;Note: Each time this routine is called, the mouse driver increments an
- ; internal counter. The MousePointerOff routine decrements the
- ; counter. The MouseReset routine set the counter to an initial
- ; value of -1. While the counter < 0 the mouse pointer will be
- ; hidden and when the counter >= 0 the pointer is visible.
- ; In other words, if MousePointerOff was called three
- ; successive times, MousePointerOn would have to be called three
- ; times before the pointer would be physically turned back on.
-
- ;From BASIC:
- ;
- ; DECLARE SUB MousePointerOn () 'This is optional.
- ;
- ; CALL MousePointerOn 'Or, if you used the DECLARE, simply
- ; MousePointerOn
-
- cmp cs:MouseButtons,0 ;Has the mouse been initialized?
- jz @F ;If not, exit.
-
- mov ax,1 ;Function 1 - Show pointer
- int 33h ;Call the mouse driver.
-
- @@: ret ;Back to BASIC.
-
- MousePointerOn endp
-
- ;-----------------------------------------------------------------------------
-
- MousePointerOff proc
-
- ;This routine makes the mouse pointer visible. Please see the special
- ;note under the MousePointerOn routine for details about the mouse
- ;driver's internal counter.
-
- ;Note: Even though the mouse pointer is not visible, the driver
- ; continues to track the mouse pointer position.
-
- ;From BASIC:
- ;
- ; DECLARE SUB MousePointerOff () 'This is optional.
- ;
- ; CALL MousePointerOff 'Or, if you used the DECLARE, simply
- ; MousePointerOff
-
- cmp cs:MouseButtons,0 ;Has the mouse been initialized?
- jz @F ;If not, exit.
-
- mov ax,2 ;Function 2 - Show mouse pointer
- int 33h ;Call the mouse driver.
-
- @@: ret ;Back to BASIC
-
- MousePointerOff endp
-
- ;-----------------------------------------------------------------------------
-
- MouseGetStatus proc, Lb:word, Rb:Word, Cb:Word, Row:Word, Column:Word
-
- ;Returns the current "real time" state of the mouse buttons and the
- ;mouse pointers current position in row/column coordinates. A value
- ;of -1 (TRUE) returned for Lb%, Rb% or Cb% indicates that the
- ;respective button is currently pressed and a value of zero (FALSE)
- ;indicates the button is not pressed.
-
- ;From BASIC:
- ;
- ; DECLARE SUB MouseGetStatus(Lb%, Rb%, Cb%, Row%, Column%) 'Optional
- ;
- ; CALL MouseGetStatus(Lb%, Rb%, Cb%, Row%, Column%) 'Or
- ; MouseGetStatus Lb%, Rb%, Cb%, Row%, Column%
-
- xor ax,ax ;Assume all buttons off
- mov bx,ax
- mov cx,ax ;Row/Column 0
- mov dx,ax
-
- cmp cs:MouseButtons,0 ;Mouse initialized?
- jz @F ;If not, exit.
-
- mov ax,3 ;Function 3 - Get status
- int 33h ;Call the mouse driver
-
- call _CommonFromPixels
-
- @@:
- call _SetupReturn
- ret ;Back to BASIC
-
- MouseGetStatus endp
-
- ;-----------------------------------------------------------------------------
-
- MouseSetPointer proc, Row:Word, Column:Word
-
- ; Set the mouse pointer position. The format for the coordinates is
- ; based on the most recent call to either of MousePixelsOn or
- ; MousePixelsOff. If neither have been previously called, row/column
- ; coordinates is the default.
-
- ; If coordinates provided are outside the physical screen or outside of
- ; the vertical or horizontal limits set by the MouseSetWindow routine,
- ; the coordinates are adjusted automatically.
-
- ; From BASIC:
- ;
- ; DECLARE SUB MouseSetPointer(Row%, Column%) 'Optional
- ;
- ; CALL MouseSetPointer(Row%, Column%) 'Or, if using the declare,
- ; MouseSetPointer Row%, Column%
-
- cmp cs:MouseButtons,0 ;Has the mouse been initialized?
- jz @F ;If not, exit.
-
- assume ds:dgroup
- mov bx,[Row] ;Pointer to Row (Vertical) into bx
- mov dx,[bx] ;Row% into dx
- mov bx,[Column] ;Pointer to Column into bx
- mov cx,[bx] ;Column% into cx
-
- call _CommonToPixels ;Convert to pixels, if necessary
-
- mov ax,4 ;Mouse function 4 - Set position
- int 33h ;Call the mouse driver
-
- @@: ret ;Back to BASIC.
-
- MouseSetPointer endp
-
- ;-----------------------------------------------------------------------------
-
- MousePressInfo proc, Button:Word, Row:Word, Column:Word
-
- ; Returns the number of times the specified mouse button has been
- ; pressed since the last time this routine was called. It also returns
- ; the position where the specified button was pressed.
-
- ; From BASIC:
- ;
- ; DECLARE FUNCTION MousePressInfo% (Button%, Row%, Column%)
- ;
- ; NumberOfPresses% = MousePressInfo%(Button%,Row%,Column%)
- ;
- ; On entry, Button% = 0 for the left button
- ; 1 for the right button
- ; 2 for the center button (if any)
- ;
- ; On exit, the result of the function indicates the number of times
- ; the specified button has been pressed since this routine was last
- ; called. Row% and Column% will contain the coordinates where the
- ; specified button was last pressed. The current coordinate system
- ; is used (See MousePixelsOn and MousePixelsOff).
-
- ;This block of code is used by the MousePressInfo and the MouseReleaseInfo
- ;routines. BX contains the function number (5 for PressInfo or 6 for
- ;release info). The common entry point is CommonButtonInfo.
-
- mov bx,5 ;Function 5 - Get pressed info
-
- CommonButtonInfo:: ;Both colons are supposed to be there
- xor ax,ax ;Zero our return registers in case
- mov cx,ax ;mouse has not been initialized. This
- mov dx,ax ;way, we'll return all zeros.
-
- cmp cs:MouseButtons,0 ;Has the mouse been initialized?
- jz @F ;If not, exit
-
- mov ax,bx ;Put function number into ax
-
- mov bx,[Button] ;Pointer to Button% into bx
- mov bx,[bx] ;Button% value into bx
-
- int 33h ;Call the mouse driver
-
- push bx ;Save bx
- call _CommonFromPixels ;Convert pixels to row/columns, if needed
- pop ax
-
- @@:
- mov bx,[Row] ;Pointer to Row% into bx
- mov [bx],dx ;Vertical position into Row%
- mov bx,[Column] ;Pointer to Column% into bx
- mov [bx],cx ;Horizontal position into Column%
- ret ;Number of presses in ax returned as
- ; result of function.
- MousePressInfo endp
-
- ;-----------------------------------------------------------------------------
-
- MouseReleaseInfo proc, Button:Word, Row:Word, Column:Word
-
- ; Returns the number of times the specified mouse button has been
- ; released since the last time this routine was called. It also returns
- ; the position where the specified button was last released.
-
- ; From BASIC:
- ;
- ; DECLARE FUNCTION MouseReleaseInfo% (Button%, Row%, Column%)
- ;
- ; NumberOfReleases% = MouseReleaseInfo%(Button%,Row%,Column%)
- ;
- ; On entry, Button% = 0 for the left button
- ; 1 for the right button
- ; 2 for the center button (if any)
- ;
- ; On exit, the result of the function indicates the number of times
- ; the specified button has been released since this routine was last
- ; called. Row% and Column% will contain the coordinates where the
- ; specified button was last released. The current coordinate system
- ; is used (See MousePixelsOn and MousePixelsOff).
-
- mov bx,6 ;Function 6 - Get Release info
- jmp short CommonButtonInfo
-
- MouseReleaseInfo endp
-
- ;-----------------------------------------------------------------------------
-
- MouseSetWindow proc,TopRow:Word,LeftColumn:Word,BottomRow:Word,RightColumn:Word
-
- ; Set the coordinates for a window in which the mouse pointer is allowed
- ; to move. By default, the pointer is allowed to move freely over the
- ; entire screen. This routine allows you to limit the mouse pointer's
- ; movement to a specific rectangular area of the screen.
-
- ; From BASIC:
- ;
- ; DECLARE SUB MouseSetWindow(TopRow%, LeftColumn%, BottomRow%,_
- ; RightColumn%)
- ;
- ; CALL MouseSetWindow(10, 10, 20, 70)
-
- cmp cs:MouseButtons,0 ;Has the mouse been initialized?
- jz @F ;If not, exit
-
- mov bx,[BottomRow] ;Pointer to BottomRow% into bx
- mov dx,[bx] ;BottomRow% into dx
- mov bx,[RightColumn] ;Pointer to RightColumn% into bx
- mov cx,[bx] ;RightColumn% into cx
- call _CommonToPixels ;Convert to pixels, if needed
- push dx ;Save BottomRow and RightColumn
- push cx ; on stack until needed later.
-
- mov bx,[TopRow] ;Pointer to TopRow% into bx
- mov dx,[bx] ;TopRow% into dx
- mov bx,[LeftColumn] ;Pointer to LeftColumn% into bx
- mov cx,[bx] ;LeftColumn% into cx
- call _CommonToPixels ;Convert to pixels, if needed
-
- mov bx,dx ;Hold TopRow in bx for now
- pop dx ;RightColumn coordinate into dx
-
- mov ax,7 ;Function 7 - Set horizontal limits
- int 33h ;Call mouse driver
-
- mov cx,bx ;TopRow into cx
- pop dx ;BottomRow into dx
-
- mov ax,8 ;Function 8 - Set vertical limits
- int 33h ;Call mouse driver
-
- @@: ret
-
- MouseSetWindow endp
-
- ;-----------------------------------------------------------------------------
-
- MouseSetHardwarePointer proc uses si, StartScan:Word, EndScan:Word
-
- ; Defines the shape and characteristics of the mouse pointer used in
- ; text video modes. The "hardware" cursor is simply a character block
- ; which the programmer can control the starting scan line
- ; and the ending scan line (i.e., the size and shape of the
- ; block). When the hardware cursor is moved over the screen, it appears
- ; as a blinking block.
-
- ;From BASIC:
- ;
- ; DECLARE SUB MouseSetHardwarePointer(StartScan%, EndScan%)
- ;
- ; CALL MouseSetHardwarePointer(0, 7)
-
- mov bx,1 ;Set hardware cursor
-
- ; The following code is shared between MouseSetHardwarePointer and
- ; MouseSetSoftwarePointer.
-
- CommonSetCursor:: ;Both colons are supposed to be there
- cmp cs:MouseButtons,0 ;Has the mouse been initialized?
- jz @F ;If not, exit.
-
- mov ax,0ah ;Function 0Ah - Set pointer attributes
- mov si,[StartScan] ;Offset of Param1 into si
- mov cx,[si] ;Param1 into cx (StartScan or AND mask)
- mov si,[EndScan] ;Offset of Param1 into si
- mov dx,[si] ;Param2 into dx (EndScan or XOR mask)
- int 33h ;Call mouse driver
-
- @@: ret
-
- MouseSetHardwarePointer endp
-
- ;-----------------------------------------------------------------------------
-
- MouseSetSoftwarePointer proc uses si, AndMask:Word, XorMask:Word
-
- ; Sets characteristics of mouse "software" pointer. This type of pointer
- ; is used only in text modes and physically manipulates whatever character
- ; and attribute that is under it. The values passed in Param1 (AND mask)
- ; and in Param2 (XOR mask) determine exactly how the character and
- ; attribute will be manipulated.
-
- ;From BASIC:
- ;
- ; DECLARE SUB MouseSetSoftwarePointer (AndMask%, XorMask%)
- ;
- ; CALL MouseSetSoftwarePointer(&H77ff, &H7700)
-
- ; The AND mask determines what part of the character/attribute pair
- ; will be passed through and the XOR mask determines which of the
- ; resulting bits will be toggled. In each case, the low byte of the
- ; integer applies to the character and the high bytes applies to the
- ; attribute.
-
- mov bx, 0
- jmp short CommonSetCursor
-
- MouseSetSoftwarePointer endp
-
- ;-----------------------------------------------------------------------------
-
- MouseMovement proc, Rows:Word, Columns:Word
-
- ; Returns the net mouse displacement since the last call to this routine.
- ; In other words, it tells you how many "mickeys" (approx 1/200th of an
- ; inch) the mouse has moved from it's position the last time this routine
- ; was called.
-
- ; From BASIC:
- ;
- ; DECLARE SUB MouseMovement (Rows%, Columns%)
- ;
- ; CALL MouseMovement (Rows%, Columns%)
-
- xor cx,cx ;Zero cx and dx so zeros will be
- mov dx,cx ;returned if mouse not initialized
-
- cmp cs:MouseButtons,0 ;Has the mouse been initialized?
- jz @F ;If not, exit.
-
- mov ax,0bh ;Function 0Bh - Read movement counters
- int 33h ;Call mouse driver
-
- @@:
- mov bx,[Rows] ;Pointer to Rows% into bx
- mov [bx],dx ;Vertical movement into Rows%
- mov bx,[Columns] ;Pointer to Columns into bx
- mov [bx],cx ;Horizontal movement into Columns%
- ret ;Back to BASIC.
-
- MouseMovement endp
-
- ;-----------------------------------------------------------------------------
-
- MouseSetRatio proc, VertRatio:word, HorizRatio:Word
-
- ; Sets the ratio between the amount mouse physical mouse movement
- ; (mickeys) and the amount of movement reflect by the mouse pointer
- ; on the screen. The value passed in reflects the number of mickeys
- ; required to move the pointer 8 pixels. The default is 8 mickeys per
- ; 8 pixels (1 mickey per pixel) horizontal and 16 mickeys per 8 pixels
- ; (2 mickeys per pixel) of vertical movement. A value between
- ; 1 and 32767 mickeys can be specified.
-
- ;From BASIC:
- ;
- ; DECLARE SUB MouseSetRatio (VertRatio%, HorizRatio%) 'Optional
- ;
- ; CALL MouseSetRatio(8, 4) 'Doubles mouse sensitivity
-
- cmp cs:MouseButtons,0 ;Has the mouse been initialized?
- jz @F ;If not, exit.
-
- mov bx,[VertRatio] ;Pointer to VertRatio% into bx
- mov dx,[bx] ;VertRatio% into dx
- mov bx,[HorizRatio] ;Pointer to HorizRatio% into bx
- mov cx,[bx] ;HorizRatio% into cx
-
- mov ax,0fh ;Function 0Fh - Set mickey/pixel ratio
- int 33h ;Call mouse driver
-
- @@: ret ;Back to BASIC
-
- MouseSetRatio endp
-
- ;-----------------------------------------------------------------------------
-
- MouseSetExclusionArea proc uses si di, TopRow:Word, LeftColumn:Word, BottomRow:Word, RightColumn:Word
-
- ; If the mouse pointer is moved into the rectangular area of the screen
- ; defined by this routine, the mouse pointer will be turned off.
-
- ;From BASIC:
- ;
- ; DECLARE SUB MouseSetExclusionArea (TopRow%, LeftColumn%, BottomRow%,_
- ; RightColumn%)
- ;
- ; CALL MouseSetExclusionArea (1, 1, 3, 80)
-
- cmp cs:MouseButtons,0 ;Has the mouse been initialized?
- jz @F ;If not, exit.
-
- mov bx,[BottomRow]
- mov dx,[bx] ;BottomRow% into dx
- mov bx,[RightColumn]
- mov cx,[bx] ;RightColumn into cx
-
- call _CommonToPixels ;Convert to pixels, if needed.
-
- mov si,cx ;Move bottom/right coordinates into
- mov di,dx ; si and di.
-
- mov bx,[TopRow]
- mov dx,[bx] ;TopRow% into dx
- mov bx,[LeftColumn]
- mov cx,[bx] ;LeftColumn% into cx
-
- call _CommonToPixels ;Convert to pixels, if needed
-
- mov ax,10h ;Function 10h - Set exclusion area
- int 33h ;Call mouse driver.
-
- @@: ret ;Back to BASIC.
-
- MouseSetExclusionArea endp
-
- ;-----------------------------------------------------------------------------
-
- MouseSetDblSpd proc, MickeysPerSecond:Word
-
- ; Sets the mouse pointer "double speed threshold". If the mouse is moved
- ; faster than the specified number of MickeysPerSecond, the mouse pointer
- ; will kick into overdrive and effectively move twice as fast. The
- ; default is 64 Mickeys (approx 1/3 inch) per second.
-
- ; Passing a large value (such as 10,000) effectively disables the
- ; speed doubling effect.
-
- ;From BASIC:
- ;
- ; DECLARE SUB MouseSetDblSpeed (MickeysPerSecond%)
- ;
- ; CALL MouseSetDblSpeed(200) 'Set it to 1 inch per second
-
- cmp cs:MouseButtons,0 ;Has mouse been initialized?
- jz @F ;If not, exit.
-
- mov bx,[MickeysPerSecond]
- mov dx,[bx] ;MickeysPerSecond% into dx
-
- mov ax,13h ;Function 13h - Set double speed threshold
- int 33h ;Call the mouse driver
-
- @@: ret ;Back to BASIC
-
- MouseSetDblSpd endp
- ;-----------------------------------------------------------------------------
-
- MouseWaitForRelease proc
-
- ; Waits for all mouse buttons to be released before returning control
- ; to the calling program.
-
- ;From BASIC:
- ;
- ; DECLARE SUB MouseWaitForRelease () 'Optional
- ;
- ; CALL MouseWaitForRelease 'Or, if declare is present,
- ; MouseWaitForRelease
-
- cmp cs:MouseButtons,0 ;Has the mouse been initialized?
- jz WaitReleaseExit ;If not, exit.
-
- @@:
- mov ax,3 ;Function 3 - Get mouse status
- int 33h ;Call Mouse driver.
- test bl,7 ;Are bit 0, 1 and 2 all off?
- jnz @B ;If not, loop until they are.
-
- WaitReleaseExit:
- ret ;Back to BASIC.
-
- MouseWaitForRelease endp
-
- ;-----------------------------------------------------------------------------
- MouseSaveState proc
-
- ; Save the current mouse state including, position, visibility, and
- ; other characteristics. You could use this routine prior to SHELLing
- ; another program which could use the mouse.
-
- ; The MouseRestoreState routine restores the previous state of the mouse.
-
- ; This routine make a call to BASIC's SETMEM code to release enough
- ; memory to DOS to save the mouse state. When the MouseRestoreState
- ; routine is CALLed, the memory is released from DOS and given back
- ; to BASIC.
-
- ; Note: This routine can be DECLAREd as a SUB or a FUNCTION. If declared
- ; as an integer FUNCTION, -1 (TRUE) is returned if the state was
- ; saved successfully and 0 (FALSE) if unsuccessful (due to
- ; insufficient memory). If you don't care about the success or
- ; failure of the operation, you can simply DECLARE it as a SUB
- ; without parameters.
- ;
- ;From BASIC:
- ;
- ; DECLARE SUB MouseSaveState ()
- ; CALL MouseSaveState
-
- ; -or-
-
- ; DECLARE FUNCTION MouseSaveState% ()
- ; IF MouseSaveState% THEN
- ; PRINT "Mouse state saved successfully"
- ; ELSE
- ; PRINT "Insufficient memory to save mouse state!"
- ; END IF
-
- cmp cs:MouseButtons,0 ;Has mouse been initialized?
- jz SaveStateExit ;If not, exit
-
- cmp cs:StateSegment,0 ;Do we already have a state saved?
- jz @F ;If not, continue
- call far ptr MouseRestoreState ;If we do, release it.
-
- @@:
- mov ax,15h ;Function 15h - Mouse save buffer size
- int 33h ;Call mouse driver
-
- add bx,32 ;Add two paragraphs (because of SETMEM)
- mov cs:SaveBytes,bx ;Save for later
- neg bx ;Make negative (SETMEM releases mem)
- mov dx,-1 ;Extend the negative sign into MSW
- push dx ;Push long int on stack
- push bx
- call B$SetM ;Do the SETMEM
-
- mov bx,cs:SaveBytes ;Restore number of bytes
- mov cl,4 ;Divide by 16 (Dos wants paragraphs)
- shr bx,cl ;Much faster than DIViding
- mov ax,4800h ;Dos allocate memory function
- int 21h ;Call DOS
- jc AllocError ;Whoops - not enough memory
-
- mov cs:StateSegment,ax ;Store it here
- xor dx,dx ;Offset of buffer area
- mov es,ax ;Segment of buffer goes here
- mov ax,16h ;Function 16h - Save mouse state
- int 33h ;Call mouse driver
- mov ax,-1 ;If declared as function, return TRUE
-
- SaveStateExit:
- ret ;Back to BASIC
-
- AllocError:
- xor ax,ax ;Zero ax so a FALSE result will be
- jmp short SaveStateExit ; returned if declared as function.
-
- MouseSaveState endp
-
- ;-----------------------------------------------------------------------------
-
- MouseRestoreState proc
-
- ; Restores the state of the mouse if previously saved with the
- ; MouseSaveState routine. See the MouseSaveState routine for additonal
- ; usage notes.
-
- ;From BASIC:
- ;
- ; DECLARE SUB MouseRestoreState () 'Optional
- ; CALL MouseRestoreState 'Or, if declare is present,
- ; MouseRestoreState
-
- cmp cs:MouseButtons,0 ;Has the mouse been initialized?
- jz @F ;If not, exit
-
- cmp cs:StateSegment,0 ;Has a state been saved?
- jz @F ;If not, exit
-
- mov ax,2 ;The restore function doesn't turn off
- int 33h ;current cursor, so we'll do it.
-
- mov es,cs:StateSegment ;Segment of buffer into es
- xor dx,dx ;Offset of buffer is zero.
- mov ax,17h ;Function 17h - Restore mouse state
- int 33h ;Call mouse driver
-
- mov ax,4900h ;Dos function 49h - Free memory block
- int 21h ;Call Dos
-
- mov ax,cs:SaveBytes ;Number of bytes BASIC gave to us
- xor dx,dx ;Zero dx
- push dx ;Push long int onto stack for SETMEM
- push ax
- call B$SetM ;Give the buffer space back to BASIC
-
- mov cs:StateSegment,0 ;Zero our variable
-
- @@: ret ;Back to BASIC
-
- MouseRestoreState endp
-
- ;-----------------------------------------------------------------------------
-
- MouseGetSensitivity proc uses si, VertRatio:Word, HorizRatio:Word, DblSpd:Word
-
- ; Returns the current mouse "sensitivity" related settings. See the
- ; routines MouseSetRatio and MouseSetDblSpd for more information
-
- ;From BASIC:
- ;
- ; DECLARE SUB MouseGetSensitivity (VertRatio%, HorizRatio%, DblSpd%)
- ; CALL MouseGetSensitivity (VertRatio%, HorizRatio%, DblSpd%)
-
- xor bx,bx ;Zero these registers. If mouse not
- mov cx,bx ; initialized, all parameters will be
- mov dx,bx ; returned with zero values.
-
- cmp cs:MouseButtons,0 ;Has mouse been initialized?
- jz @F ;If not, exit
-
- mov ax,1bh ;Function 1Bh - Get mouse sensitivity
- int 33h ;Call mouse driver
-
- @@:
- mov si,[VertRatio]
- mov [si],cx ;Move data in cx to VertRatio%
- mov si,[HorizRatio]
- mov [si],bx ;Data in bx to HorizRatio%
- mov si,[DblSpd]
- mov [si],dx ;Double-speed ratio into DblSpd%
- ret
-
- MouseGetSensitivity endp
-
- ;-----------------------------------------------------------------------------
-
- MouseGetPage proc
-
- ; Returns the display page the mouse pointer is currently visible on. See
- ; MouseSetPage to change the pointer's current display page. Returns -1
- ; if the mouse has not yet been initialized.
-
- ;From BASIC:
- ;
- ; DECLARE FUNCTION MouseGetPage% ()
- ;
- ; PRINT "The current pointer display page is"; MouseGetPage%
-
- mov bx, -1 ;Assume NOT initialized
-
- cmp cs:MouseButtons,0 ;Has the mouse been initialized?
- jz @F ;If not, exit
-
- mov ax,1eh ;Function 1Eh - Get pointer page
- int 33h ;Call the mouse driver
-
- @@:
- mov ax,bx ;Put result in ax for return
- ret ;Back to BASIC.
-
- MouseGetPage endp
-
- ;-----------------------------------------------------------------------------
-
- MouseSetPage proc, PointerPage:Word
-
- ; Sets the current mouse pointer display page. Be sure that your current
- ; video mode supports the specified page number. See BASIC's SCREEN
- ; statement documention for more info.
-
- ;From BASIC:
- ;
- ; DECLARE SUB MouseSetPage(PointerPage%) 'Optional
- ; CALL MouseSetPage(1) 'Or, if the declare is present,
- ; MouseSetPage 1
-
- cmp cs:MouseButtons,0 ;Has the mouse been initialized?
- jz @F ;If not, exit
-
- mov bx,[PointerPage]
- mov bx,[bx] ;Put Page% into bx
-
- mov ax,1dh ;Function 1Dh - Select pointer page
- int 33h ;Call mouse driver
-
- @@: ret ;Back to BASIC
-
- MouseSetPage endp
-
- ;-----------------------------------------------------------------------------
-
- MouseGetInfo proc uses si, MajorV:word, MinorV:Word, MouseType:Word, Irq:Word
-
- ; Returns information about the current mouse hardware and software:
-
- ; MajorVer% - The Major mouse driver version (7 for 7.04). It is returned
- ; as zero if the mouse has not been initialized.
-
- ; MinorVer% - The Minor mouse driver version (4 for 7.04)
-
- ; MouseType% - 1 = bus mouse, 2 = serial mouse, 3 = InPort mouse,
- ; 4 = PS/2 mouse, 5 = HP mouse
-
- ; Irq% - The hardware Irq line that the mouse driver is using. 0 = PS/2,
- ; or 2, 3, 4, 5, or 7 for all others.
-
- ;From BASIC:
- ;
- ; DECLARE SUB MouseGetInfo(MajorV%, MinorV%, MouseType%, Irq%)
- ; CALL MouseGetInfo(MajorV%, MinorV%, MouseType%, Irq%)
-
- xor bx,bx ;Zero registers so results will be
- mov cx,bx ;returned as zero if not initialized.
-
- cmp cs:MouseButtons,0 ;Has the mouse been initialized?
- jz @F ;If not, exit
-
- mov ax,24h ;Function 24h - Get mouse information
- int 33h ;Call mouse driver
-
- @@:
- xor ah,ah ;Make sure ah = 0
- mov al,bh ;Major version into al
- mov si,[MajorV]
- mov [si],ax ;Ax into MajorV%
- mov al,bl ;Minor version into al
- mov si,[MinorV]
- mov [si],ax ;Ax into MinorV%
- mov al,ch ;Mouse type into al
- mov si,[MouseType]
- mov [si],ax ;Ax into MouseType%
- mov al,cl ;Irq into al
- mov si,[Irq]
- mov [si],ax ;Ax into Irq%
- ret
-
- MouseGetInfo endp
- ;-----------------------------------------------------------------------------
-
- MouseSetEvent proc, EventMask:Word
-
- ; This routine sets up a "Mouse Event" handler which can be trapped in
- ; your BASIC program via "ON UEVENT".
-
- ; The following are the available events that can be trapped. Any
- ; combination of events are acceptable. Each event has a value
- ; associated with it. Define the desired event by assigning its
- ; value to the EventMask% parameter when calling this routine. Combinations
- ; of events can be obtained by adding the values of the respective events.
- ; for example, to set an event for "left button release" and "right
- ; button release", simply add the values together: 4 + 16 = 20.
-
- ; 1 = Any mouse movement
- ; 2 = Left button pressed
- ; 4 = Left button released
- ; 8 = Right button pressed
- ; 16 = Right button released
- ; 32 = Center button pressed
- ; 64 = Center button released
-
- ;From BASIC:
- ;
- ; DECLARE SUB MouseSetEvent (EventMask%)
- ; CALL MouseSetEvent(20) 'Traps left or right button release
- ;
- ; ON UEVENT GOSUB MouseEvent
- ; UEVENT ON
- ;
- ; DO 'Continue processing event until
- ; A$ = INKEY$ ' a key is pressed.
- ; LOOP UNTIL LEN(A$)
- ; END
- ;
- ;MouseEvent:
- ; CALL MouseGetEventInfo(Event%, Lb%, Rb%, Cb%, Row%, Column%)
- ; PRINT "Mouse event occurred: - ";
- ; IF Event% AND 4 THEN
- ; PRINT "Left Button was released."
- ; END IF
- ; IF Event% AND 16 THEN
- ; PRINT "Right Button was released."
- ; END IF
- ; PRINT "Mouse location:"; Row%; ","; Column%
- ;RETURN
-
- cmp cs:MouseButtons,0 ;Has mouse been initialized?
- jz @F ;If not, exit
-
- Assume ds:Dgroup
- mov bx,[EventMask] ;Pointer to EventMask% into bx
- mov cx,[bx] ;EventMask% into cx
- jcxz @F ;Don't allow zero. Use MouseCancelEvent
- and cx,127 ; to disable handler. Strip unused bits
- call _SetEventHandler ;Turn on mouse event handler
- mov cs:UEventActive,-1 ;Set our flag indicating active event
-
- @@: ret ;Back to BASIC.
-
- MouseSetEvent endp
-
- ;-----------------------------------------------------------------------------
-
- MouseCancelEvent proc
-
- ; Cancels (disables) active mouse event handler.
-
- ; From BASIC:
- ;
- ; DECLARE SUB MouseCancelEvent () 'Optional
- ; CALL MouseCancelEvent 'Or if declare is present,
- ; MouseCancelEvent
-
- cmp cs:UEventActive,0 ;Is the event handler active?
- jz @F ;If not, exit
-
- xor cx,cx ;Zero cx (Disables handler)
- call _SetEventHandler ;Call the mouse driver
- mov cs:UEventActive,0 ;Zero our flag
-
- @@: ret ;Back to BASIC
-
- MouseCancelEvent endp
-
- ;-----------------------------------------------------------------------------
-
- MouseGetEventInfo proc, Event:Word, Lb:Word, Rb:Word, Cb:Word, Row%:Word, Column:Word
-
- ;Returns the values set during the last mouse event
-
- ;From BASIC:
- ;
- ; DECLARE SUB MouseGetEventInfo(Event%, Lb%, Rb%, Cb%, Row%, Column%)
- ; CALL MouseGetEventInfo(Event%, Lb%, Rb%, Cb%, Row%, Column%)
-
- ; Event% is bit-mapped and indicates what condition(s) triggered the
- ; mouse event. Just "AND" Event% with a value associated with one of
- ; your defined events. If the result is non-zero then that was what
- ; triggered the event. For example:
- ;
- ; PRINT "Event cause: ";
- ; IF Event% AND 4 THEN '4 is value for "left release"
- ; PRINT "Left button was released."
- ; ELSEIF Event% AND 16 THEN '16 is value for "right release"
- ; PRINT "Right button was released."
- ; END IF
-
- ; See MouseSetEvent for a complete listing of all available events and
- ; their respective values.
-
- ; The other parameters reflect the state of the mouse at the time of the
- ; last event. See MouseSetStatus for info on how to interpret their
- ; meanings.
-
- xor ax,ax ;Zero registers so zero results will
- mov bx,ax ; returned if the mouse has not been
- mov cx,ax ; initialized.
- mov dx,ax
-
- cmp cs:MouseButtons,0 ;Has the mouse been initialized?
- jz @F ;If not, exit
-
- mov bx,cs:ButtonState ;Load registers with current values
- mov cx,cs:HorizPos ; set by the last event.
- mov dx,cs:VertPos
-
- call _CommonFromPixels ;Convert to row/column, if needed
-
- @@:
- call _SetupReturn ;Load register contents into params
- mov ax,cs:EventCause ; for return to BASIC.
- Assume ds:Dgroup
- mov bx,[Event] ;Pointer to Event% into bx
- mov [bx],ax ;Event mask into Event%
- ret
-
- MouseGetEventInfo endp
-
- ;-----------------------------------------------------------------------------
-
- MouseExit proc
-
- ; This code should be called prior to program termination. It performs
- ; such tasks as releasing memory allocated by the mouse routines and
- ; unhooking the mouse routines from the mouse driver's "User Defined Event"
- ; handler. Failure to call this routine prior to program termination
- ; could result is a system lockup if the MouseSetEvent routine has been
- ; previously called and the MouseCancelEvent routine was not.
-
- ; During the call to the MouseReset routine, we attempted to add this
- ; this routine to BASIC's B_OnExit chain. This allows BASIC itself to call
- ; this code when your program terminates or restarts. In other words,
- ; you probably won't have to worry about it. It is a pretty rare occurance
- ; that the B_OnExit call would fail - more than 32 other procedures would
- ; have to be registered before it would fail.
-
- ; But for those faint of heart, we've gotcha covered. The function
- ; MouseOnExit% returns true if we are successfully included
- ; in the B_OnExit chain. If it returns false, the you need to call
- ; this routine (MouseExit) manually before your program terminates. For
- ; example:
-
- ; IF NOT MouseOnExit% THEN
- ; CALL MouseExit
- ; END IF
- ; END
-
- cmp cs:MouseButtons,0 ;Has mouse been initialized?
- jz @F ;If not, get out
-
- cmp cs:StateSegment,0 ;Has mouse state been saved and not
- jz CheckEventHandler ; restored? If not, continue.
-
- mov es,cs:StateSegment ;Put its segment into es
- mov ax,4900h ;Dos function 49h - Release memory
- int 21h ;Call Dos.
-
- mov cs:StateSegment,0 ;Zero the flag in case in the IDE
-
- xor ax,ax ;Set up for call to SETMEM. Give back
- push ax ; memory to BASIC. This is necessary
- push cs:SaveBytes ; in case we are in the environment
- call b$SetM ; where the memory isn't automatically
- ; reclaimed.
- CheckEventHandler:
- cmp cs:UEventActive,0 ;Is a mouse event sent?
- jz @F ;If not, exit
-
- xor cx,cx ;Cancel mouse event handler
- call _SetEventHandler
-
- mov cs:UEventActive,0 ;Clear our event flag
- mov cs:OnExitSet,0 ;Clear our OnExit flag. (We're
- ; supposedly terminating the program)
- @@: ret ;Back to whoever called us
-
- MouseExit endp
-
- ;-----------------------------------------------------------------------------
- ; The procedures listed below are called internally by the various mouse
- ; routines. Do not attempts to call these from BASIC.
- ;-----------------------------------------------------------------------------
-
- _CommonToPixels proc near
-
- ;Converts row/column coordinates to pixel based coordinates.
-
- cmp cs:PixelsOn,-1 ;Are we in the Pixels mode?
- jz @F ;If so, skip.
-
- call _GetCharSize ;Returns size of char in pixels
-
- xchg ax,dx ;Vertical location into ax
- dec ax ;Decrement by 1 for base 0 calculation
- xor dx,dx ;Zero dx for multiplication
- mul bx ;Multiply
- xchg ax,cx ;Horiz position into ax and result of
- dec ax ; last calculation into cx.
- xor dx,dx ;Zero dx again for another multiply
- mov bx,8 ;Multiply by 8 pixels wide
- mul bx
- xchg dx,cx ;Results of first calc back into dx
- xchg ax,cx ;Result of last calc into cx
-
- @@: ret
-
- _CommonToPixels endp
-
- ;-----------------------------------------------------------------------------
-
- _CommonFromPixels proc near uses es
-
- ;Internal routine that converts mouse pixel corrdinates into row/column
- ;coordinates.
-
- ;Enter with BX = button status
- ; CX = Horizontal (X) position in pixels
- ; DX = Vertical (Y) position in pixels
- ;Returns: AH = Left button status
- ; AL = Right Button Status
- ; BH = Center button status
-
- cmp cs:PixelsOn,-1 ;Is pixel mode on?
- jz @F ;If so, skip the row/col conversion
-
- push bx ;Save button status for now
- call _GetCharSize ;Interrogate system for char size
- xchg ax,dx ;Vertical position into ax
- xor dx,dx ;Zero dx for division
- div bx ;Divide by char height -> ax
- inc ax ;Add 1
- push ax ;Save result for now
- mov bx,8 ;Character width into bx for divide
- xchg cx,ax ;Put horizontal position into ax
- xor dx,dx ;Zero dx again for division
- div bx ;Divide position by char width -> ax
- inc ax ;Add 1
- xchg cx,ax ;Result back into cx
- pop dx ;Result of first calculation into dx
- pop bx ;Restore button status.
-
- @@:
- call _XlateButtonStatus ;Convert bx into Lb, Rb and Cb
- ret ;We're finished here.
-
- _CommonFromPixels endp
-
- ;-----------------------------------------------------------------------------
-
- _GetCharSize proc near
-
- ;Internal routine that returns the character height (in scan lines)
- ;in the BX register.
-
- push ds ;Save ds
- mov ax,40h
- Assume Ds:Nothing
- mov ds,ax ;Point ds to BIOS Data Area
- mov bl,byte ptr ds:[84h] ;Ega/Vga rows into bl
- cmp bl,0 ;If non-zero, we are on a EGA/MCGA/VGA
- jz CgaOrMono ;If zero, it's a CGA, mono, or Herc.
- mov bl,ds:[49h] ;Get current video mode
- cmp bl,3 ;If >3 we're in graphics mode
- jg GraphicsMode ;Jump to that code, if needed
- mov bx,8 ;If in text mode, char size is 8
- jmp short HeightExit
-
- GraphicsMode:
- mov bx,ds:[85h] ;Get info right from BIOS data area.
- jmp short HeightExit ;We're finished.
-
- CgaOrMono:
- mov bx,8 ;Always 8 high
-
- HeightExit:
- pop ds ;Restore ds as to not freak anyone out
- ret ;Back to whatever procedure called us
-
- _GetCharSize endp
-
- ;-----------------------------------------------------------------------------
-
- _XlateButtonStatus proc near
-
- ;Converts BX into button status info. Returned in AH (LB), AL (RB), and
- ; BH (CB).
-
- xor ax,ax ;Zero ax and bh (assume all off)
- mov bh,ah
- test bl,1 ;Is left button pressed?
- jz CheckRight ;If not, check next button
- not ah ;If it is pressed, make ah = -1
-
- CheckRight:
- test bl,2 ;Is the right button pressed?
- jz CheckCenter ;If not, check center button
- not al ;If it is pressed, make al = -1
-
- CheckCenter:
- test bl,4 ;Is the center button pressed?
- jz ExitButtonStatus ;If not, exit.
- not bh ;If so, make bh=-1
-
- ExitButtonStatus:
- ret
-
- _XlateButtonStatus endp
-
- ;-----------------------------------------------------------------------------
-
- _SetupReturn proc near
-
- ; Internal routine that takes register values, coverts them to words,
- ; and loads them into BASIC parameters for return.
-
- Assume ds:DGroup
- push ax ;Save two copies of ax
- push ax
- mov al,bh ;move bh into al (so we can use bx)
- cbw ;Convert al to a word (extends sign)
- mov bx,[bp+10] ;Pointer to Cb% into bx
- mov [bx],ax ;Center button status into Cb%
- pop ax
- cbw ;Convert al to word (Right button)
- mov bx,[bp+12] ;Pointer to Rb% into bx
- mov [bx],ax ;Right button status into Rb%
- pop ax
- mov al,ah ;Left button status into al
- cbw ;Convert it to a word
- mov bx,[bp+14] ;Pointer to Lb% into bx
- mov [bx],ax ;Left button status into Lb%
- mov bx,[bp+8] ;Pointer to Row% into bx
- mov [bx],dx ;Vertical position into Row%
- mov bx,[bp+6] ;Pointer to Column% into bx
- mov [bx],cx ;Horizontal position into Row%
- ret
-
- _SetupReturn endp
-
- ;-----------------------------------------------------------------------------
-
- _MouseEventHandler proc uses ds
-
- ; This routine is called by the mouse driver when the MouseSetEvent routine
- ; has been previously called. Each time, we call BASIC's SetUEvent routine,
- ; store the mouse button status and location for later retrieval -
- ; presumably during the BASIC program's "ON UEVENT" handler.
-
- ; On entry, the registers are configured as follows:
- ;
- ; AX - Mouse event flag(s). See MouseSetEvent for more info.
- ; BX - Current button status
- ; CX - Horizontal (X) mouse pointer location
- ; DX - Vertical (Y) mouse pointer location
- ; SI - Last raw vertical mickey count
- ; DI - Last raw horizontal mickey count
- ; DS - Mouse driver data segment
-
- mov cs:EventCause,ax ;Save event mask (cause of event)
- mov cs:ButtonState,bx ;Save button state
- mov cs:VertPos,dx ;Current vertical position
- mov cs:HorizPos,cx ;Current horizontal position
- push ss
- pop ds ;Point ds to DGROUP for call
- call SetUEvent ;Tell BASIC a "UEvent" occurred.
- ret ;Return to mouse driver
-
- _MouseEventHandler endp
-
- ;-----------------------------------------------------------------------------
-
- _SetEventHandler proc near
-
- ; Internal routine - Used to establish or cancel an active mouse
- ; event handler.
-
- ; Input: CX - Event Mask. 0 Cancels, 1-127 establishes
-
- mov ax,0ch ;Function 0Ch - Set mouse event handler
- push cs ;Point to the one we want to disable.
- pop es
- mov dx,offset _MouseEventHandler
- int 33h ;Call the mouse driver
- ret
-
- _SetEventHandler endp
-
- ;-----------------------------------------------------------------------------
- end ;End of assembly source file
-