Frage deutsch
~~~~~~~~~~~~~
Wie binde ich die Maus in mein Programm ein?
Question English
~~~~~~~~~~~~~
How do I support the mouse in my QBasic program?
Antwort 1
~~~~~~~~~
[ von Thomas Antoni, 15.5.2002 ]
.
Lade Dir von www.qbasic.de das
"Rundum-Sorglos-Mauspaket" MAUS.ZIP herunter. Es steht dort in der Rubrik
"Download -> Maus&Tastatur" zur Verfügung.
In dem ZIP-Archiv findest Du die 4 besten und beliebtesten Maus-Routinen für
QBasic für den Grafik- und den Text-Screen. Da ist für jeden etwas dabei:
Mausroutinen für QBasic, QuickBASIC, den Text-SCREEN und die Grafik-SCREENs.
Darüber hinaus ist das sehr gute deutsche "Tutorial zur Nutzung der Maus unter
QuickBasic" von Dankrad Feist enthalten.
Viele Maustreiber verwenden den Befehl CALL ABSOLUTE, was beim Aufruf des
programms unter QuickBasic 4.5 zu einer Fehlermeldung führt, wenn man die
"QuickLibrary" QB.QLB nicht mit einbindet (bei QBasic nicht erforderlich). Um
diesen Fehler zu vermeiden muss man QuickBasic 4.5 mit dem Parameter /L
starten.
Unter DOS sieht das dann so aus:
qb /L meinprog.bas
Aus Windows heraus startet man einfach den Eigenschaftendialog von QB.EXE mit
der rechten Maustaste und gibt unter "Eigenschaften | Programm | Befehlszeile"
den folgenden Text ein:
...\QB.EXE /L
Dann funktionieren alle Maustreiber und sonstigen Programme, die den CALL
ABSOLUTE oder den INTERRUPT(X) Befehl verwenden, problemlos.
Antwort 2
~~~~~~~~~
[ von Michael Frey ( m.frey*bluemail.ch ) , 28.4.02 -
12.6.02 ]
.
Wenn Du eine eine einfache Mausroutine suchst, die narrensicher funktioniert,
dann kann ich Dir eine Empfehlung geben:
Untenstehend findest Du meine Lieblings-Maus-Routine! Sie funktionert bei
QBasic 1.1 QB 4.5 und 7.1 (mit /L starten wegen CALL ABSOLUTE)
Die Mausroutine ist getestet unter Windows 95, 98 und NT4. Du kannst Dein
Anwenderprogramm zwischen die Befehlszeilen
WHILE INKEY$ CHR$(27) 'beenden mit ESC
Mouse x, y, t
und
WEND
einfügen, also statt der beiden LOCATE .. PRINT .. -Befehle
In den Variablen x und y findest Du die Position des Mauszeigers pixelgenau
und in "t" die gedrückte Taste
Die beiden Zeilen
LOCATE 1: PRINT "Position der Maus:"; x; y
LOCATE 2: PRINT "Taste:"; t
kannst Du in der Beta-Version Deines Anwenderprogramms noch 'drin lassen, um
das "Debugging" zu erleichtern. Danach kannst Du sie unbesorgt löschen.
Noch ein kleiner Hinweis diese Mauroutine läuft außer in SCREEN 12 auch in
den SCREENS 7, 8, 9, 11 und 13.
Diese Mausroutine ist nicht von mir, ich benutze sie einfache gerne, weil sie
so schön kurz ist und in allen Lebenslagen robust funktioniert!
... Und so sieht die Mausroutine aus:
'*************************************************************
' MOUSE.BAS - Mausprogramm fuer den Grafikmodus
' =========
' Die Mausroutinen funtionieren in den Grafikmodi SCREENS
' 7, 8, 9, 11, 12 und 13 unter QBasic 1.1 und QuickBASIC
' 4.5 & 7.1. Da der Befehl CALL ABSOLUTE verwendet wird,
' muss QuickBASIC mit dem Parameter "/L" aufgerufen werden,
' also z.B. ueber QB /L mouse.bas. Bei QBasic ist dies nicht
' erforderlich
'
' Die Routinen wurden getestet unter unter Windows 95, 98
' und NT4.
'
' Du kannst Dein Anwenderprogramm zwischen die Befehls-
' zeilen WHILE INKEY$ CHR$(27)
' Mouse x, y, t
' und WEND
' einfuegen, also statt der beiden LOCATE .. PRINT..-Befehle
'
' In den Variablen x und y findest Du die pixelgenaue
' Position des Mauszeigers pixelgenau und in "t" die
' gedrueckte Maustaste.
' Die beiden Zeilen
' LOCATE 1: PRINT "Position der Maus:"; x; y
' LOCATE 2: PRINT "Taste:"; t
' kannst Du in der Beta-Version Deines Anwenderprogramms
' noch drin lassen, um das "Debugging" zu erleichtern.
' Danach kannst Du sie unbesorgt loeschen.
'
' von Paul S. Mueller
' Email: Mueller-Staufenberg*t-online.de
' Webseite: www.psm-home.2xs.de
'************************************************************
'
'Maustasten-Status in der Variablen t:
'linke = 1 ; linke + mittlere = 5
'rechte = 2 ; rechte + mittlere = 6
'linke + rechte = 3 ; alle = 7
'mittlere = 4
'
DEFINT A-Z
DECLARE SUB Mouse (x, y, t)
DECLARE SUB MousePointer (SW)
DIM SHARED a(9)
DEF SEG = VARSEG(a(0))
FOR i = 0 TO 17
READ r
POKE VARPTR(a(0)) + i, r
NEXT i
DATA &HB8,&H00,&H00 : DATA &H55 : DATA &H8B,&HEC
DATA &HCD,&H33 : DATA &H92 : DATA &H8B,&H5E,&H06
DATA &H89,&H07 : DATA &H5D : DATA &HCA,&H02,&H00
'
SCREEN 12
MousePointer 0
MousePointer 1 'aktiviert den Mauszeiger
MousePointer 3
WHILE INKEY$ <> CHR$(27) 'beenden mit ESC
Mouse x, y, t
LOCATE 1: PRINT "Position der Maus:"; x; y
LOCATE 2: PRINT "Taste:"; t
WEND
MousePointer 2 'deaktiviert die Maus
DEF SEG
END
'
SUB Mouse (dx, cx, bx)
POKE VARPTR(a(4)), &H92
CALL absolute(cx, VARPTR(a(0)))
POKE VARPTR(a(4)), &H91
CALL absolute(dx, VARPTR(a(0)))
POKE VARPTR(a(4)), &H93
CALL absolute(bx, VARPTR(a(0)))
END SUB
'
SUB MousePointer (SW)
POKE VARPTR(a(0)) + 1, SW
CALL absolute(c, VARPTR(a(0)))
END SUB
Das obige Programm steht im Verzeichnis Progs\ zur Verfügung sowie online
unter www.antonis.de/faq/progs/mouse.bas .
Antwort 3
~~~~~~~~~~~~~~~~
[ von Roman Zoller ("greenbit" - info*greenbit.ch - www.greenbit.ch ) , 12.3.03 ]
Wie einfach das Einbinden der Maus in QuickBASIC geht, zeigt mein folgendes
Programm:
'****************************************************************************
' MAUS.BAS = Einfach zu verwendende Mausroutine fuer QuickBASIC
' ========
' Die Einbindung der Maus in QuickBASIC ist ganz einfach! Das zeigt die
' in diesem Programm integrierte Subroutine "treiber". In diesem
Beispiel-
' programm werden die Mauskoordinaten und Klicks angezeigt. Das Programm
' eignet sich sowohl fuer Grafik-Screens als auch fuer den
textbvildschirm
' SCREEN 0.
'
' HINWEISe
' - Dieses Beispiel funktioniert nur in QuickBASIC 4.5, nicht in QBasic,
' da der INTERRUPT-Befehl verwendet wird.
' - QuickBASIC muss mit der Option /l qb.qlb gestartet werden.
' - Wenn etwas "unter" die Maus gezeichnet werden soll, dann muss diese
' kurz deaktiviert werden. Im Beispiel würde dieses Deaktivieren etwa
' so aussehen:
' treiber 2, 0, 0, 0
' ... Hier kommen Befehle zum Zeichnen auf den Bildschirm
' treiber 1, 0, 0, 0
'****************************************************************************
DEFINT A-Z
TYPE RegType
ax AS INTEGER
bx AS INTEGER
cx AS INTEGER
dx AS INTEGER
bp AS INTEGER
si AS INTEGER
di AS INTEGER
flags AS INTEGER
END TYPE
DECLARE SUB INTERRUPT (intnum AS INTEGER, inreg AS RegType, outreg AS
RegType)
DECLARE SUB treiber (ax, bx, cx, dx)
'
SCREEN 12
'
LOCATE 1, 1
PRINT "Links", "Mitte", "Rechts", "x (Spalte)", "y (Zeile)"
'
treiber 1, 0, 0, 0
'
DO
treiber 3, bx, cx, dx
'
LOCATE 2, 1
PRINT ((bx AND 1) <> 0), ((bx AND 4) <> 0), ((bx AND 2) <>
0), cx, dx
LOOP UNTIL INKEY$ <> ""
'
SUB treiber (ax, bx, cx, dx)
DIM regs AS RegType
regs.ax = ax
regs.bx = bx
regs.cx = cx
regs.dx = dx
INTERRUPT &H33, regs, regs
ax = regs.ax
bx = regs.bx
cx = regs.cx
dx = regs.dx
END SUB
Das obige Programm steht im Verzeichnis Progs\ zur Verfügung sowie online
unter www.antonis.de/faq/progs/maus.bas .
Antwort 4
~~~~~~~~~~~~~~~~~
[ von Herbert Hackelsberger ( www.hackelsberger.at ) per Mail am
7.10.2001 ]
Man kann die Maus in QuickBASIC mit Systemaufrufen direkt unterstützen. Dazu
benötigt man den Interrupt &H33. Mann muss es so machen:
'**************************************************
' MAUS2.BAS = Einfache Mausroutine fuer QuickBASIC
' =========
' Dieses Programm realisert eine Mausunter-
' stuetzung in QuickBASIC. Unter QBasic ist es
' nicht ablauffaehig. Es werden der Maustasten-
' Status und die Mauskoordinaten engezeigt.
' Durch Druecken einer beliebigen Taste wird das
' Programm beendet.
'
' Weil das Programm den INTERRUPT-Befehl
' verwendet, muss QuickBASIC muss mit der
' Option /L gestartet werden, z.B. mit
' QB.EXE /L MAUS2.BAS
'
' (c) Herbert Hackelsberger, 7.10.2001
'***************************************************
'
REM $INCLUDE: 'qb.bi'
DIM indat AS REGTYPE, ausdat AS REGTYPE
SCREEN 12
indat.ax = &H0
CALL INTERRUPT(&H33, indat, ausdat)
indat.ax = &H1
CALL INTERRUPT(&H33, indat, ausdat)
indat.ax = &H3
DO
CALL INTERRUPT(&H33, indat, ausdat)
LOCATE 1, 1
PRINT ausdat.bx, ausdat.cx, ausdat.dx
'Tastenstatus und Mauskoordinaten anzeigen
LOOP UNTIL INKEY$ <> ""
ausdat.bx = 1
Das obige Programm steht im Verzeichnis Progs\ zur Verfügung sowie online
unter www.antonis.de/faq/progs/maus2.bas .
Answer 5
~~~~~~~~~
For this, calls to the mouse driver have to be made. Click here to see an
example of how you can shape your own mouse cursor in text mode, and how to make
buttons on the screen work. The author is Wouter Bergmann Tiest mailto:
W.M.BergmannTiest*fys.ruu.nl.
Answer 6
~~~~~~~~~
[ by Douggie Green ( douggie*blissinx.demon.co.uk ), 1995 ]
My follwing mouse routines use Interrupts and also work in text mode SREEN
0:
'***************************************************************************
' MOUSEINT.BAS = Mouse routines for QBasic using interrupts
' ============ Mausroutinen fuer QBasic mit Interrupts
'
' MOUSEINT.BAS - demonstrates mouse usage in QBasic, utilizing code from
' Brent Ashley's QBasic Toolbox. The text screen SCREEN 0 is used.
' INT-DEMO.BAS - shows how to use interrupts. Ralf Brown's interrupt list
' is probably the most comprehensive in existence, and it's *very* big.
' Available from SimTel and other sites.
'
' Also includes scanword$(x,y), a function which returns the word under
' the cursor.
'
' Plus DIR$, a function which returns matching file names. *Very* useful.
' Contributed by Ian Musgrave.
'
' To use these routines with QB4/QB4.5 follow these instructions :-
' Rename Regs to InRegs in the declaration section.
' Define another variable of type RegTypeX as OutRegs
' Change 'interrupt &H33, Regs' to 'CALL interrupt (&H33, InRegs,
OutRegs)'
' Rename Regs to InRegs for parameters passed to the interrupt, and
rename
' Regs to OutRegs for values returned from the interrupt.
' Delete SUB Interrupt () and the DATA statements.
'
' Feel free to modify and improve this code, and keep my name out of it!
' Enjoy, Douggie
'
' (c) Douggie Green ( douggie*blissinx.demon.co.uk ), 1995
'****************************************************************************
DECLARE SUB GetMousePos (xp%, yp%)
DECLARE FUNCTION ButtonStatus% (b$)
DECLARE FUNCTION buttonrelease% (b$)
DECLARE SUB pause ()
DECLARE SUB SetMousePos (xmpos%, ympos%)
DECLARE FUNCTION InitMouse% ()
DECLARE SUB showmouse ()
DECLARE SUB hidemouse ()
DECLARE FUNCTION scanword$ (x%, y%)
'
DEFINT A-Z
'
TYPE RegTypeX
AX AS INTEGER
bx AS INTEGER
CX AS INTEGER
DX AS INTEGER
BP AS INTEGER
SI AS INTEGER
DI AS INTEGER
Flags AS INTEGER
DS AS INTEGER
ES AS INTEGER
END TYPE
DIM SHARED Regs AS RegTypeX
DECLARE SUB INTERRUPT (IntNum%, Regs AS RegTypeX)
DECLARE FUNCTION DIR$ (FileSpec$)
'----- Some constants that DIR$ uses
CONST DOS = &H21 'Interupt &H21
CONST SetDTA = &H1A00, FindFirst = &H4E00, FindNext = &H4F00
DIM FileArray$(1 TO 500) 'This is only set to 500 files, there
'can be more, to find the number of files
'to exactly dimension the array requires
'calling DIR$ twice. (once to count, once
'to put into the array
'
CLS
mousebuttons = InitMouse '' This will usually return 2, even with 3
button
'' mice <dg>
'
IF mousebuttons = 0 THEN
PRINT "Mouse not present"
END
END IF
'
PRINT mousebuttons; " button mouse detected"
CALL SetMousePos(30, 10) '' x,y format, based on 80x25 screen
'
showmouse
LOCATE 12, 1
PRINT "Click on a word (any word). Press any key to move on."
DO ''end when any key is pressed <dg>
CALL GetMousePos(xmpos, ympos)
LOCATE 1, 1: PRINT " "
LOCATE 1, 1: PRINT "mouse is at "; xmpos, ympos
button = ButtonStatus("l")
LOCATE 2, 1: PRINT " "
LOCATE 2, 1: PRINT "Button status "; button
'
''-------------------------------scanword example code----------------
button = buttonrelease("l")
IF button = 1 THEN
comm$ = scanword$((xmpos), (ympos)) ''We don't want to change xmpos
LOCATE 15, 30
PRINT " ";
LOCATE 15, 30
PRINT comm$
END IF
''----------------------------end of scanword example-----------------
a$ = INKEY$
LOOP WHILE a$ = ""
'
hidemouse
'
pause
'
END
'
''hex data for interrupt routines
'
DATA &H55, &H8B, &HEC, &H83, &HEC, &H08, &H56,
&H57, &H1E, &H55, &H8B, &H5E
DATA &H06, &H8B, &H47, &H10, &H3D, &HFF, &HFF,
&H75, &H04, &H1E, &H8F, &H47
DATA &H10, &H8B, &H47, &H12, &H3D, &HFF, &HFF,
&H75, &H04, &H1E, &H8F, &H47
DATA &H12, &H8B, &H47, &H08, &H89, &H46, &HF8,
&H8B, &H07, &H8B, &H4F, &H04
DATA &H8B, &H57, &H06, &H8B, &H77, &H0A, &H8B,
&H7F, &H0C, &HFF, &H77, &H12
DATA &H07, &HFF, &H77, &H02, &H1E, &H8F, &H46,
&HFA, &HFF, &H77, &H10, &H1F
DATA &H8B, &H6E, &HF8, &H5B, &HCD, &H21, &H55,
&H8B, &HEC, &H8B, &H6E, &H02
DATA &H89, &H5E, &HFC, &H8B, &H5E, &H06, &H1E,
&H8F, &H46, &HFE, &HFF, &H76
DATA &HFA, &H1F, &H89, &H07, &H8B, &H46, &HFC,
&H89, &H47, &H02, &H89, &H4F
DATA &H04, &H89, &H57, &H06, &H58, &H89, &H47,
&H08, &H89, &H77, &H0A, &H89
DATA &H7F, &H0C, &H9C, &H8F, &H47, &H0E, &H06,
&H8F, &H47, &H12, &H8B, &H46
DATA &HFE, &H89, &H47, &H10, &H5A, &H1F, &H5F,
&H5E, &H8B, &HE5, &H5D, &HCA
DATA &H02, &H00
'
'------------------------------end INTMOUSE.BAS-----------------------
Douggie Green (douggie*blissinx.demon.co.uk)
FUNCTION buttonrelease (b$)
Regs.AX = &H6
IF LEFT$(UCASE$(b$), 1) = "L" THEN Regs.bx = 0 ELSE Regs.bx = 1
INTERRUPT &H33, Regs
'
buttonrelease = Regs.bx '' Count of releases, reset to 0 each call.
END FUNCTION
'
FUNCTION ButtonStatus (b$)
'' b$ should be either "l" or "r". When called once, will return the
'' number of times the specified button has been pressed since the last
'' call. When used in a loop, as in this demo prog, it works like INKEY$
'' Could be split into ButtonDown() and ButtonCount() <dg>
'
Regs.AX = &H5
IF LEFT$(UCASE$(b$), 1) = "L" THEN Regs.bx = 0 ELSE Regs.bx = 1
INTERRUPT &H33, Regs
'
ButtonStatus = Regs.bx '' Count of presses, reset to 0 each call.
'
IF Regs.AX > 0 THEN ButtonStatus = Regs.AX '' Is a button down?
''if so, return which button
END FUNCTION
'
FUNCTION DIR$ (FileSpec$) STATIC
'
'' Contributed by Ian Musgrave - Ian.Musgrave*med.monash.edu.au
'
DIM DTA AS STRING * 44 ', Regs AS RegTypeX
Null$ = CHR$(0)
'----- Set up our own DTA so we don't destroy COMMAND$
Regs.AX = SetDTA 'Set DTA function
Regs.DX = VARPTR(DTA) 'DS:DX points to our DTA
Regs.DS = -1 'Use current value for DS
INTERRUPT DOS, Regs 'Do the interrupt
'
'----- Check to see if this is First or Next
IF LEN(FileSpec$) THEN 'FileSpec$ isn't null, so
'FindFirst
FileSpecZ$ = FileSpec$ + Null$ 'Make FileSpec$ into an ASCIIZ
'string
Regs.AX = FindFirst 'Perform a FindFirst
Regs.CX = 0 'Only look for normal files
Regs.DX = SADD(FileSpecZ$) 'DS:DX points to ASCIIZ file
Regs.DS = -1 'Use current DS
ELSE 'We have a null FileSpec$,
Regs.AX = FindNext 'so FindNext
END IF
'
INTERRUPT DOS, Regs 'Do the interrupt
'
'----- Return file name or null
IF Regs.Flags AND 1 THEN 'No files found
DIR$ = "" 'Return null string
ELSE
Null = INSTR(31, DTA, Null$) 'Get the filename found
DIR$ = MID$(DTA, 31, Null - 30) 'It's an ASCIIZ string starting
END IF 'at offset 30 of the DTA
'
END FUNCTION
'
SUB GetMousePos (xp, yp)
Regs.AX = &H3
INTERRUPT &H33, Regs
xp = Regs.CX / 8 '' These values may need changing depending on
yp = Regs.DX / 8 '' your screen mode <dg>
END SUB
'
SUB hidemouse
Regs.AX = &H2
INTERRUPT &H33, Regs
END SUB
'
FUNCTION InitMouse
Regs.AX = &H0
INTERRUPT &H33, Regs
IF Regs.AX <> 0 THEN InitMouse = Regs.bx ELSE InitMouse = 0
END FUNCTION
'
SUB INTERRUPT (IntNum, Regs AS RegTypeX) STATIC
STATIC FileNum, IntOffset, Loaded
'
' use fixed-length string to fix its position in memory
' and so we don't mess up string pool before routine
' gets its pointers from caller
DIM IntCode AS STRING * 200
IF NOT Loaded THEN ' loaded will be 0 first time
'
FOR k = 1 TO 145
READ h%
MID$(IntCode, k, 1) = CHR$(h%)
NEXT
'
'' determine address of interrupt no. offset in IntCode
IntOffset = INSTR(IntCode$, CHR$(&HCD) + CHR$(&H21)) + 1
Loaded = -1
END IF
SELECT CASE IntNum
CASE &H25, &H26, IS > 255 ' ignore these interrupts
CASE ELSE
DEF SEG = VARSEG(IntCode) ' poke interrupt number into
POKE VARPTR(IntCode) * 1& + IntOffset - 1, IntNum ' code block
CALL Absolute(Regs, VARPTR(IntCode$)) ' call routine
END SELECT
END SUB
SUB pause
WHILE a$ = ""
a$ = INKEY$
WEND
END SUB
'
FUNCTION scanword$ (x, y)
y = y + 1: x = x + 1 '' need to adjust because the mouse routines return
'' values >= 0, and LOCATE and SCREEN need >=1
hidemouse
c = SCREEN(y, x) ''Get the character under the mouse cursor
''and check it's alphanumeric, or punctuation
IF c > 39 AND c < 123 THEN ''We're over a word so...
LOCATE y, x
DO ''Find the start of the word
c = SCREEN(y, x)
x = x - 1
LOOP UNTIL c < 39 OR c > 123 OR x = 0
IF x > 0 THEN x = x + 2 ''We end up at the x position *before* the
''word, so adjust again.
IF x = 0 THEN x = 1 ''SCREEN and LOCATE need this, just in case.
DO ''Read the word
c = SCREEN(y, x)
w$ = w$ + CHR$(c)
x = x + 1
LOOP UNTIL c < 39 OR c > 123 OR x = 0
w$ = LEFT$(w$, LEN(w$) - 1) ''We end up past the word, so trim it.
END IF
'
scanword$ = w$
showmouse
END FUNCTION
'
SUB SetMousePos (xmpos, ympos)
Regs.AX = &H4
Regs.CX = xmpos * 8 '' These values may need changing depending on
Regs.DX = ympos * 8 '' your screen mode <dg>
INTERRUPT &H33, Regs
END SUB
'
SUB showmouse
Regs.AX = &H1
INTERRUPT &H33, Regs
END SUB
Das obige Programm steht im Verzeichnis Progs\ zur Verfügung sowie online
unter www.antonis.de/faq/progs/mouseint.bas .
Answer 8
~~~~~~~~
[ from The Official FidoNet Quick Basic Echo's FAQ, Edited by Greg Easthom (
greg_easthom*bandmaster.bc.ca ), Dec
15, 1999 ]
HOW DO I USE THE MOUSE IN QB?
The most common (and most universal) approach is through INTERRUPTs. Using
INTERRUPT 33h, the following code will allow you to use a mouse in your
programs. Code by David Aukerman with the idea for limited mouse movement by
Dave Shea. Public domain; use at your own risk!
'$INCLUDE: 'qb.bi' 'these three lines go at the
DEFINT A-Z 'beginning of your program..
DIM SHARED HMin, HMax, VMin, VMax 'horiz. and vert. limits
'
SUB Mouse (cx, dx, bx)
DIM reg AS RegType
reg.ax = 3 'get coordinates
INTERRUPT &H33, reg, reg
bx = reg.bx '1=left button; 2=right; 3=both
'(on a two button mouse)
cx = reg.dx 'horizontal coordinate in *pixels*
dx = reg.cx 'vertical coordinate in *pixels*
END SUB
'
SUB MouseCtrl (x)
DIM reg AS RegType
reg.ax = x '0 = initialize/reset mouse
'1 = show cursor
'2 = hide cursor
'3 = get current coordinates
'7 = set horizontal coordinates
'8 = set vertical coordinates
IF x = 7 THEN
reg.cx = HMin: reg.dx = HMax
ELSEIF x = 8 THEN
reg.cx = VMin: reg.dx = VMax
END IF
INTERRUPT &H33, reg, reg
END SUB
Here are my mouse routines working in QuickBASIC, QBasic and all SREEN
modes:
'*******************************************************************
' MOUSE2.BAS = Mouse routines for QBasic, works in all SCRREN modes
' ========== Maus-Routinen fuer QBasic, funktioniert in allen
' SCREEN-Modi
'
' Deutsche Beschreibung
' ----------------------
' Diese Mausroutinen funktionieren nicht nur unter QuickBASIC,
' sondern auch unter QBasic 1.1, weil der CALL ABSOLUTE statt des
' CALL INTERRUPT-Befehls verwendet wird. Das Demo-Programm arbeitet
' im Grafik-SCREEN 13. Die Routinen sind aber auch in allen anderen
' Bildschirmmodi inkl. SCREEN 0 verwendbar.
'
' English Description
' ----------------------
' This is a collection of subs (and one function) that I wrote so people
' can easily use the mouse in their program by just adding the subs to
' their program.
'
' These don't use CALL INTERRUPT (which is only supported by QuickBASIC,
' not by asic), but instead uses CALL ABSOLUTE which is compatiable with
' Qbasic 1.1. (I prefer INTERRUPT, but I wanted compatiablity)
'
' If you just want the code, copy and paste! heh :)
'
' The MouseDriver sub is what makes the actual call to interrupt 33, but
' you don't need to call it directly. Instead, use the other subs I
' provide.
'
' The example here demonstrates each of the subs I've created.
'
' (c) by /\lipha - aliphax*hotmail.com - www.geocities.com/aliphax
'*********************************************************************
DECLARE SUB MouseDriver (ax AS INTEGER, bx AS INTEGER, cx AS INTEGER, dx AS
INTEGER)
DECLARE FUNCTION MouseExists% ()
DECLARE SUB MouseShow ()
DECLARE SUB MouseHide ()
DECLARE SUB MouseStatus (mouseX, mouseY, leftB, rightB, middleB)
DECLARE SUB MousePosition (newX, newY)
DECLARE SUB MouseSetArea (x1, y1, x2, y2)
DECLARE SUB MouseLastPress (button, x, y)
CONST TRUE = -1
CONST FALSE = 0
CONST LEFT = 0 'the buttons (you pass one of these to
CONST RIGHT = 1 'MouseLastPress to find out the location
CONST CENTER = 2 'of the last click of the left, right, or
'center button)
'
'the Machine code routine used by MouseDriver
MouseData:
DATA 55,89,E5,8B,76,06,8B,14,8B,76,08,8B,0C,8B,76,0A
DATA 8B,1C,8B,76,0C,8B,04,1E,07,CD,33,8B,76,06,89,14
DATA 8B,76,08,89,0C,8B,76,0A,89,1C,8B,76,0C,89,04,5D
DATA CA,08,00
'
'
'Above code is needed for the mouse routines along with
'the Mouse subs and functions
'
'The below code is a "test frame" to demonstrate the mouse
'routines. You can delete it and add your own code
'(I recommend deleting the below code of the main program
'preserving the SUBs and then save this file.
'Then you can open up this file whenever you want to make
'a program using the mouse)
'
'
'
SCREEN 13
CLS
'set the area of the screen that the mouse can move in
MouseSetArea 300, 50, 639, 199
MouseShow
'
DO
'get the (x, y) coordinates of the mouse and the left and right
'button status (can also get the middle button [if you have one]
'but this call doesn't. To do so, replace 0 with a variable)
MouseStatus x, y, lb, rb, 0
'
LOCATE 1, 1
PRINT x, y
PRINT lb, rb
'
k$ = INKEY$
IF k$ = "s" THEN MouseShow
IF k$ = "h" THEN MouseHide
'
'press the "c" key to center the mouse on the screen
'(at coordinate (320,100))
IF k$ = "c" THEN MousePosition 320, 100
'
'get the location on the screen of where the last time
'you pressed the left button was (if hasn't been pressed,
'the x and y = -1)
IF k$ = "p" THEN
MouseLastPress LEFT, x, y
PRINT x, y
END IF
'
LOOP UNTIL k$ = CHR$(27) 'press Esc to end
'
MouseHide
'
SCREEN 0
WIDTH 80, 25
END
'
'
SUB MouseDriver (ax AS INTEGER, bx AS INTEGER, cx AS INTEGER, dx AS
INTEGER)
STATIC called AS INTEGER, mouseDrv AS STRING
DIM mCount AS INTEGER, mData AS STRING
'
IF NOT called THEN 'the first time this sub is called, there is some
called = TRUE 'initialization that needs to be done
RESTORE MouseData
'
FOR mCount = 1 TO 51
READ mData
mouseDrv = mouseDrv + CHR$(VAL("&H" + mData))
NEXT mCount
'
'checks for mouse driver
IF NOT MouseExists THEN PRINT "No Mouse Driver": END
END IF
'
DEF SEG = VARSEG(mouseDrv)
CALL ABSOLUTE(ax, bx, cx, dx, SADD(mouseDrv))
DEF SEG
END SUB
'
FUNCTION MouseExists%
DIM ax AS INTEGER
ax = 0
MouseDriver ax, 0, 0, 0
'
MouseExists% = ax
END FUNCTION
'
SUB MouseHide
MouseDriver 2, 0, 0, 0
END SUB
'
SUB MouseLastPress (button, x, y)
DIM bx AS INTEGER, cx AS INTEGER, dx AS INTEGER
'
IF button <> LEFT AND button <> RIGHT AND button <> MIDDLE
THEN
x = -1
y = -1 'if you passed an invalid parameter
EXIT SUB
END IF
'
bx = button
MouseDriver 5, bx, cx, dx
'
IF bx = 0 THEN 'if the button hasn't been pressed
x = -1
y = -1
ELSE
x = cx
y = dx
END IF
'
END SUB
'
SUB MousePosition (newX, newY)
DIM cx AS INTEGER, dx AS INTEGER
cx = newX
dx = newY
MouseDriver 4, 0, cx, dx
END SUB
'
SUB MouseSetArea (x1, y1, x2, y2)
DIM cx AS INTEGER, dx AS INTEGER
cx = x1 'set horizontal range
dx = x2
MouseDriver 7, 0, cx, dx
cx = y1 'set vertical range
dx = y2
MouseDriver 8, 0, cx, dx
END SUB
'
SUB MouseShow
MouseDriver 1, 0, 0, 0
END SUB
'
SUB MouseStatus (mouseX, mouseY, leftB, rightB, middleB)
DIM bx AS INTEGER, cx AS INTEGER, dx AS INTEGER
MouseDriver 3, bx, cx, dx
'
'the bits in bx contain the button status
'bit 0 = left; bit 1 = right; bit 2 = middle
IF (bx AND 1) THEN leftB = TRUE ELSE leftB = FALSE
IF (bx AND 2) THEN rightB = TRUE ELSE rightB = FALSE
IF (bx AND 4) THEN middleB = TRUE ELSE middleB = FALSE
'
mouseX = cx
mouseY = dx
END SUB
Das obige Programm steht im Verzeichnis Progs\ zur Verfügung sowie online
unter www.antonis.de/faq/progs/mouse2.bas .
Answer 10
~~~~~~~~~
How do I use the mouse in QBasic?
It's sort of tough to explain here, so let's just do this the plain and easy
way, use a premade mouse program, check out the Mouse/Joystick section of QCity.