microsoft quickbasic v4
This commit is contained in:
parent
195806130b
commit
b791cd023a
118
Microsoft QuickBASIC v4/ABSOLUTE.ASM
Normal file
118
Microsoft QuickBASIC v4/ABSOLUTE.ASM
Normal file
@ -0,0 +1,118 @@
|
||||
TITLE ABSOLUTE - helper for assembly routines
|
||||
;***
|
||||
; ABSOLUTE - Helper for calling BASIC interpreter assembly routines
|
||||
;
|
||||
; Copyright <C> 1986, Microsoft Corporation
|
||||
;
|
||||
;Purpose:
|
||||
; Allow a BASIC program to call a routine which is located at an
|
||||
; absolute memory address in the DEF SEG.
|
||||
;
|
||||
; The form of the call is:
|
||||
;
|
||||
; CALL ABSOLUTE(<param>,...,<loc>)
|
||||
;
|
||||
; where
|
||||
; <param>,... - zero or more parameters for the assembly routine
|
||||
; <loc> - an Integer variable that contains the
|
||||
; location in the DEF SEG of the start of
|
||||
; the assembly routine
|
||||
;
|
||||
; The location parameter will be removed, and the routine at DEF SEG:<loc>
|
||||
; will be called with the remaining parameters.
|
||||
;
|
||||
; Notes:
|
||||
; - The parameters are not checked or verified before being passed
|
||||
; to the assembly routine.
|
||||
; - CALL must be used. CALLS will cause execution to jump to a
|
||||
; random location.
|
||||
; - The DOSSEG, .MODEL, .CODE, and .DATA? directives are part of
|
||||
; the simplified segment system of MASM 5.0. If you have an
|
||||
; earlier version of MASM, you must modify the source to define
|
||||
; the segments required by Microsoft high-level languages. These
|
||||
; segments are discussed in Appendix C of "Learning and Using
|
||||
; QuickBASIC."
|
||||
;
|
||||
;******************************************************************************
|
||||
;
|
||||
DOSSEG ;requires MASM 5.0 or higher
|
||||
.MODEL medium
|
||||
|
||||
; Define the routine as public.
|
||||
|
||||
PUBLIC ABSOLUTE
|
||||
|
||||
; Define the seg segment
|
||||
|
||||
.DATA?
|
||||
|
||||
EXTRN b$seg:WORD ;seg segment
|
||||
|
||||
;***
|
||||
; ABSOLUTE - Call absolute address
|
||||
;
|
||||
;Purpose:
|
||||
; Routine which can be directly called from the basic level which in turn
|
||||
; calls an absolute address.
|
||||
;
|
||||
;Entry:
|
||||
; The actual number of parameters is variable, and depends on the routine
|
||||
; that ABSOLUTE will in turn call. The LAST parameter pushed MUST be the DS
|
||||
; offset of an integer variable containing the offset of the routine to be
|
||||
; called. The current DEF SEG is used as the segment for the call.
|
||||
;
|
||||
;Exit:
|
||||
; Whatever the called routine elects. We do NOT return here.
|
||||
;
|
||||
;Uses:
|
||||
; This routine follows convention, but does no saving or checking of the code
|
||||
; actually called.
|
||||
;
|
||||
;Notes:
|
||||
; The called routine receives control with all parameters passed to ABSOLUTE,
|
||||
; except the offset integer, on the stack in Pascal convention. The return
|
||||
; address present is back to the BASIC level code which CALLed ABSOLUTE.
|
||||
;
|
||||
; Stack on call to ABSOLUTE:
|
||||
;
|
||||
;
|
||||
; \ Variable number of parameters \
|
||||
; | to routine to be CALLed |
|
||||
; +--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+
|
||||
; | Near pointer to I2 var containing |
|
||||
; | the offset of the routine to CALL |
|
||||
; +--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+
|
||||
; |CS |
|
||||
; + Far return address to caller of ABSOLUTE +
|
||||
; [SP] -> |IP |
|
||||
; +--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+
|
||||
;
|
||||
; Stack on transfer to called routine:
|
||||
;
|
||||
; \ Variable number of parameters \
|
||||
; | to routine to be CALLed |
|
||||
; +--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+
|
||||
; |CS |
|
||||
; + Far return address to caller of ABSOLUTE +
|
||||
; [SP] -> |IP |
|
||||
; +--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+
|
||||
;
|
||||
;******************************************************************************
|
||||
|
||||
.CODE
|
||||
|
||||
ABSOLUTE PROC FAR
|
||||
|
||||
POP AX ;return offset
|
||||
POP DX ;return segment
|
||||
POP BX ;get pointer to routine address
|
||||
PUSH DX ;restore return address
|
||||
PUSH AX
|
||||
PUSH [b$seg] ;stack DEF SEG segment
|
||||
PUSH [BX] ;stack routine offset
|
||||
|
||||
RET ;jump to ABSOLUTE routine
|
||||
|
||||
ABSOLUTE ENDP
|
||||
|
||||
END
|
BIN
Microsoft QuickBASIC v4/BC.EXE
Normal file
BIN
Microsoft QuickBASIC v4/BC.EXE
Normal file
Binary file not shown.
BIN
Microsoft QuickBASIC v4/BCOM40.LIB
Normal file
BIN
Microsoft QuickBASIC v4/BCOM40.LIB
Normal file
Binary file not shown.
BIN
Microsoft QuickBASIC v4/BQLB40.LIB
Normal file
BIN
Microsoft QuickBASIC v4/BQLB40.LIB
Normal file
Binary file not shown.
BIN
Microsoft QuickBASIC v4/BRUN40.EXE
Normal file
BIN
Microsoft QuickBASIC v4/BRUN40.EXE
Normal file
Binary file not shown.
BIN
Microsoft QuickBASIC v4/BRUN40.LIB
Normal file
BIN
Microsoft QuickBASIC v4/BRUN40.LIB
Normal file
Binary file not shown.
56
Microsoft QuickBASIC v4/DEMO1.BAS
Normal file
56
Microsoft QuickBASIC v4/DEMO1.BAS
Normal file
@ -0,0 +1,56 @@
|
||||
5 DEFINT A-Z
|
||||
10 ' BASICA/GWBASIC Version of Sound Effects Demo Program
|
||||
15 '
|
||||
20 ' Sound effect menu
|
||||
25 Q = 2
|
||||
30 WHILE Q >= 1
|
||||
35 CLS
|
||||
40 PRINT "Sound effects": PRINT
|
||||
45 COLOR 15, 0: PRINT " B"; : COLOR 7, 0: PRINT "ouncing"
|
||||
50 COLOR 15, 0: PRINT " F"; : COLOR 7, 0: PRINT "alling"
|
||||
55 COLOR 15, 0: PRINT " K"; : COLOR 7, 0: PRINT "laxon"
|
||||
60 COLOR 15, 0: PRINT " S"; : COLOR 7, 0: PRINT "iren"
|
||||
65 COLOR 15, 0: PRINT " Q"; : COLOR 7, 0: PRINT "uit"
|
||||
70 PRINT : PRINT "Select: ";
|
||||
75 Q$ = INPUT$(1): Q = INSTR("BFKSQbfksq", Q$) ' Get valid key
|
||||
80 IF Q = 0 GOTO 75
|
||||
85 CLS ' Take action based on key
|
||||
90 ON Q GOSUB 100, 200, 300, 400, 500, 100, 200, 300, 400, 500
|
||||
95 WEND
|
||||
100 ' Bounce - loop two sounds down at decreasing time intervals
|
||||
105 HTONE = 32767: LTONE = 246
|
||||
110 PRINT "Bouncing . . ."
|
||||
115 FOR COUNT = 60 TO 1 STEP -2
|
||||
120 SOUND LTONE - COUNT / 2, COUNT / 20
|
||||
125 SOUND HTONE, COUNT / 15
|
||||
130 NEXT COUNT
|
||||
135 RETURN
|
||||
200 ' Fall - loop down from a high sound to a low sound
|
||||
205 HTONE = 2000: LTONE = 550: DELAY = 500
|
||||
210 PRINT "Falling . . ."
|
||||
215 FOR COUNT = HTONE TO LTONE STEP -10
|
||||
220 SOUND COUNT, DELAY / COUNT
|
||||
225 NEXT COUNT
|
||||
230 RETURN
|
||||
300 ' Klaxon - alternate two sounds until a key is pressed
|
||||
305 HTONE = 987: LTONE = 329
|
||||
310 PRINT "Oscillating . . ."
|
||||
315 PRINT " . . . press any key to end."
|
||||
320 WHILE INKEY$ = ""
|
||||
325 SOUND HTONE, 5: SOUND LTONE, 5
|
||||
330 WEND
|
||||
335 RETURN
|
||||
400 ' Siren - loop a sound from low to high to low
|
||||
405 HTONE = 780: RANGE = 650
|
||||
410 PRINT "Wailing . . ."
|
||||
415 PRINT " . . . press any key to end."
|
||||
420 WHILE INKEY$ = ""
|
||||
425 FOR COUNT = RANGE TO -RANGE STEP -4
|
||||
430 SOUND HTONE - ABS(COUNT), .3
|
||||
435 COUNT = COUNT - 2 / RANGE
|
||||
440 NEXT COUNT
|
||||
445 WEND
|
||||
450 RETURN
|
||||
500 ' Quit
|
||||
505 END
|
||||
|
76
Microsoft QuickBASIC v4/DEMO2.BAS
Normal file
76
Microsoft QuickBASIC v4/DEMO2.BAS
Normal file
@ -0,0 +1,76 @@
|
||||
DEFINT A-Z
|
||||
' QB2 Version of Sound Effects Demo Program
|
||||
' (works under most other BASIC compilers)
|
||||
|
||||
' Sound effects menu
|
||||
WHILE Q$ <> "Q"
|
||||
CLS
|
||||
PRINT "Sound effects": PRINT
|
||||
COLOR 15, 0: PRINT " B"; : COLOR 7, 0: PRINT "ouncing"
|
||||
COLOR 15, 0: PRINT " F"; : COLOR 7, 0: PRINT "alling"
|
||||
COLOR 15, 0: PRINT " K"; : COLOR 7, 0: PRINT "laxon"
|
||||
COLOR 15, 0: PRINT " S"; : COLOR 7, 0: PRINT "iren"
|
||||
COLOR 15, 0: PRINT " Q"; : COLOR 7, 0: PRINT "uit"
|
||||
PRINT : PRINT "Select: ";
|
||||
|
||||
' Get valid key
|
||||
Q$ = " "
|
||||
WHILE INSTR("BFKSQbfksq", Q$) = 0
|
||||
Q$ = INPUT$(1)
|
||||
WEND
|
||||
|
||||
' Take action based on key
|
||||
CLS
|
||||
IF Q$ = "B" OR Q$ = "b" THEN
|
||||
PRINT "Bouncing . . . "
|
||||
CALL Bounce(32767, 246)
|
||||
ELSEIF Q$ = "F" OR Q$ = "f" THEN
|
||||
PRINT "Falling . . . "
|
||||
CALL Fall(2000, 550, 500)
|
||||
ELSEIF Q$ = "S" OR Q$ = "s" THEN
|
||||
PRINT "Wailing . . ."
|
||||
PRINT " . . . press any key to end."
|
||||
CALL Siren(780, 650)
|
||||
ELSEIF Q$ = "K" OR Q$ = "k" THEN
|
||||
PRINT "Oscillating . . ."
|
||||
PRINT " . . . press any key to end."
|
||||
CALL Klaxon(987, 329)
|
||||
ELSEIF Q$ = "q" THEN
|
||||
Q$ = "Q"
|
||||
END IF
|
||||
WEND
|
||||
END
|
||||
|
||||
' Loop two sounds down at decreasing time intervals
|
||||
SUB Bounce (Hi, Low) STATIC
|
||||
FOR Count = 60 TO 1 STEP -2
|
||||
SOUND Low - Count / 2, Count / 20
|
||||
SOUND Hi, Count / 15
|
||||
NEXT
|
||||
END SUB
|
||||
|
||||
' Loop down from a high sound to a low sound
|
||||
SUB Fall (Hi, Low, Del) STATIC
|
||||
FOR Count = Hi TO Low STEP -10
|
||||
SOUND Count, Del / Count
|
||||
NEXT
|
||||
END SUB
|
||||
|
||||
' Alternate two sounds until a key is pressed
|
||||
SUB Klaxon (Hi, Low) STATIC
|
||||
WHILE INKEY$ = ""
|
||||
SOUND Hi, 5
|
||||
SOUND Low, 5
|
||||
WEND
|
||||
END SUB
|
||||
|
||||
' Loop a sound from low to high to low
|
||||
SUB Siren (Hi, Rng) STATIC
|
||||
WHILE INKEY$ = ""
|
||||
FOR Count = Rng TO -Rng STEP -4
|
||||
SOUND Hi - ABS(Count), .3
|
||||
Count = Count - 2 / Rng
|
||||
NEXT
|
||||
WEND
|
||||
END SUB
|
||||
|
79
Microsoft QuickBASIC v4/DEMO3.BAS
Normal file
79
Microsoft QuickBASIC v4/DEMO3.BAS
Normal file
@ -0,0 +1,79 @@
|
||||
DECLARE SUB Bounce (Hi%, Low%)
|
||||
DECLARE SUB Fall (Hi%, Low%, Del%)
|
||||
DECLARE SUB Siren (Hi%, Range%)
|
||||
DECLARE SUB Klaxon (Hi%, Low%)
|
||||
DEFINT A-Z
|
||||
|
||||
' QB4 Version of Sound Effects Demo Program
|
||||
|
||||
' Sound effects menu
|
||||
DO
|
||||
CLS
|
||||
PRINT "Sound effects": PRINT
|
||||
COLOR 15, 0: PRINT " B"; : COLOR 7, 0: PRINT "ouncing"
|
||||
COLOR 15, 0: PRINT " F"; : COLOR 7, 0: PRINT "alling"
|
||||
COLOR 15, 0: PRINT " K"; : COLOR 7, 0: PRINT "laxon"
|
||||
COLOR 15, 0: PRINT " S"; : COLOR 7, 0: PRINT "iren"
|
||||
COLOR 15, 0: PRINT " Q"; : COLOR 7, 0: PRINT "uit"
|
||||
PRINT : PRINT "Select: ";
|
||||
|
||||
' Get valid key
|
||||
DO
|
||||
Q$ = UCASE$(INPUT$(1))
|
||||
LOOP WHILE INSTR("BFKSQ", Q$) = 0
|
||||
|
||||
' Take action based on key
|
||||
CLS
|
||||
SELECT CASE Q$
|
||||
CASE IS = "B"
|
||||
PRINT "Bouncing . . . "
|
||||
Bounce 32767, 246
|
||||
CASE IS = "F"
|
||||
PRINT "Falling . . . "
|
||||
Fall 2000, 550, 500
|
||||
CASE IS = "S"
|
||||
PRINT "Wailing . . ."
|
||||
PRINT " . . . press any key to end."
|
||||
Siren 780, 650
|
||||
CASE IS = "K"
|
||||
PRINT "Oscillating . . ."
|
||||
PRINT " . . . press any key to end."
|
||||
Klaxon 987, 329
|
||||
CASE ELSE
|
||||
END SELECT
|
||||
LOOP UNTIL Q$ = "Q"
|
||||
END
|
||||
|
||||
' Loop two sounds down at decreasing time intervals
|
||||
SUB Bounce (Hi%, Low%) STATIC
|
||||
FOR Count = 60 TO 1 STEP -2
|
||||
SOUND Low - Count / 2, Count / 20
|
||||
SOUND Hi, Count / 15
|
||||
NEXT Count
|
||||
END SUB
|
||||
|
||||
' Loop down from a high sound to a low sound
|
||||
SUB Fall (Hi%, Low%, Del%) STATIC
|
||||
FOR Count = Hi TO Low STEP -10
|
||||
SOUND Count, Del / Count
|
||||
NEXT Count
|
||||
END SUB
|
||||
|
||||
' Alternate two sounds until a key is pressed
|
||||
SUB Klaxon (Hi%, Low%) STATIC
|
||||
DO WHILE INKEY$ = ""
|
||||
SOUND Hi, 5
|
||||
SOUND Low, 5
|
||||
LOOP
|
||||
END SUB
|
||||
|
||||
' Loop a sound from low to high to low
|
||||
SUB Siren (Hi%, Range%)
|
||||
DO WHILE INKEY$ = ""
|
||||
FOR Count = Range TO -Range STEP -4
|
||||
SOUND Hi - ABS(Count), .3
|
||||
Count = Count - 2 / Range
|
||||
NEXT Count
|
||||
LOOP
|
||||
END SUB
|
||||
|
31
Microsoft QuickBASIC v4/E.BAS
Normal file
31
Microsoft QuickBASIC v4/E.BAS
Normal file
@ -0,0 +1,31 @@
|
||||
100 DIGITS% = 200
|
||||
110 DIM A%( 200 )
|
||||
120 HIGH% = DIGITS%
|
||||
130 X% = 0
|
||||
140 N% = HIGH% - 1
|
||||
150 IF N% <= 0 GOTO 200
|
||||
160 A%[ N% ] = 1
|
||||
170 N% = N% - 1
|
||||
180 GOTO 150
|
||||
200 A%[ 1 ] = 2
|
||||
210 A%[ 0 ] = 0
|
||||
220 IF HIGH% <= 9 GOTO 400
|
||||
230 HIGH% = HIGH% - 1
|
||||
235 N% = HIGH%
|
||||
240 IF N% = 0 GOTO 300
|
||||
250 A%[ N% ] = X% MOD N%
|
||||
255 rem PRINT "a[n-1]"; A%[ N% - 1 ]
|
||||
260 X% = ( 10 * A%[ N% - 1 ] ) + ( X% \ N% )
|
||||
265 rem PRINT "x: "; X%, "n: "; N%
|
||||
270 N% = N% - 1
|
||||
280 GOTO 240
|
||||
300 IF X% >= 10 GOTO 330
|
||||
310 PRINT USING "#"; X%;
|
||||
320 GOTO 220
|
||||
330 PRINT USING "##"; X%;
|
||||
340 GOTO 220
|
||||
400 PRINT ""
|
||||
410 PRINT "done"
|
||||
420 SYSTEM
|
||||
|
||||
|
BIN
Microsoft QuickBASIC v4/FIXSHIFT.COM
Normal file
BIN
Microsoft QuickBASIC v4/FIXSHIFT.COM
Normal file
Binary file not shown.
358
Microsoft QuickBASIC v4/INTRPT.ASM
Normal file
358
Microsoft QuickBASIC v4/INTRPT.ASM
Normal file
@ -0,0 +1,358 @@
|
||||
TITLE INTERRUPT - BASCOM software interrupt calling routine
|
||||
PAGE 56,132
|
||||
;***
|
||||
; INTERRUPT - BASCOM software interrupt calling routine
|
||||
;
|
||||
; Copyright <C> 1986, 1987 Microsoft Corporation
|
||||
;
|
||||
;Purpose:
|
||||
; Allows a BASIC program to invoke an interrupt through a CALL statement.
|
||||
;
|
||||
; INTERRUPT allows BASIC to set AX,BX,CX,DX,BP,SI,DI, and the flags
|
||||
; before the call. INTERRUPTX also allows DS and ES to be set.
|
||||
; Both routines will return the values of the registers upon the
|
||||
; completion of a successful call. If the interrupt could not
|
||||
; be generated (due to a bad interrupt number or an illegal array)
|
||||
; then the interrupt number will be set to -1 to indicate an error.
|
||||
;
|
||||
;******************************************************************************
|
||||
;
|
||||
;Note:
|
||||
; The DOSSEG, .MODEL, .CODE, and .DATA? directives used in this program
|
||||
; are part of the simplified segment system of MASM 5.0. If you have
|
||||
; an earlier version of MASM, you must modify the source to define
|
||||
; the segments required by Microsoft high-level languages. These
|
||||
; segments are discussed in Appendix C of "Learning and Using QuickBASIC."
|
||||
;
|
||||
|
||||
DOSSEG ;requires MASM 5.0 or higher
|
||||
.MODEL medium
|
||||
|
||||
; Define all publicly accessible routines.
|
||||
|
||||
PUBLIC INTERRUPT, INTERRUPTX
|
||||
|
||||
; Frame structure definition
|
||||
|
||||
ARG1 = 0AH ;pointer to first of three arguments
|
||||
ARG2 = 08H ;pointer to second of three arguments
|
||||
ARG3 = 06H ;pointer to third of three arguments
|
||||
|
||||
; Frame temp variables
|
||||
|
||||
UCODE_FLGS = -02H ;user code flag register value
|
||||
UCODE_DS = -04H ;user code DS register value
|
||||
REG_NUM = -06H ;number of regs used (INTERRUPT=8, INTERRUPTX=10)
|
||||
INT_ES = -08H ;INT ES register value
|
||||
INT_DS = -0AH ;INT DS register value
|
||||
INT_FLGS = -0CH ;INT flags register value
|
||||
INT_DI = -1EH ;INT DI register value
|
||||
INT_SI = -10H ;INT SI register value
|
||||
INT_BP = -12H ;INT BP register value
|
||||
INT_DX = -14H ;INT DX register value
|
||||
INT_CX = -16H ;INT CX register value
|
||||
INT_BX = -18H ;INT BX register value
|
||||
INT_AX = -1AH ;INT AX register value
|
||||
OLD_SI = -1CH ;save old SI for interpreter
|
||||
OLD_DI = -1EH ;save old DI for interpreter
|
||||
|
||||
FRM_SIZ = -1EH ;negative size of frame temporaries
|
||||
|
||||
; Locations past frame allocation used to recover post-INT BP value.
|
||||
|
||||
INT_BP_TMP = -22H ;temp location for INT BP register value
|
||||
|
||||
;***
|
||||
; INTERRUPT, and INTERRUPTX - BASCOM software interrupt calling interface
|
||||
;
|
||||
; Purpose:
|
||||
; To allow a BASIC Compiler program to perform any software
|
||||
; interrupt. The interrupt is executed with the registers
|
||||
; set to values specified in a register variable. The post-
|
||||
; interrupt values of the registers are then stored in
|
||||
; another register variable.
|
||||
;
|
||||
; CALL INTERRUPT[X] (int_no AS INTEGER,
|
||||
; inreg AS RegType[X],
|
||||
; outreg AS RegType[X])
|
||||
;
|
||||
; Inputs:
|
||||
; int_no = interrupt number (range 0 to 255) to execute
|
||||
; inreg and outreg are register variables of type RegType[X]
|
||||
; defined as follows;
|
||||
;
|
||||
; 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
|
||||
;
|
||||
;
|
||||
; 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
|
||||
;
|
||||
; Outputs:
|
||||
; If no error:
|
||||
; int_no = unchanged (range 0 to 255)
|
||||
; outreg: This array will be set to the post-interrupt
|
||||
; register values. It has the same structure
|
||||
; as inreg.
|
||||
; If error:
|
||||
; int_no = -1
|
||||
; outreg unchanged. INT call is not performed.
|
||||
; error occurs:
|
||||
; first argument not 0 to 255 (2^8-1)
|
||||
; second or third arguments not 0 to 1048575 (2^20-1)
|
||||
; (VARPTR will always be in this range)
|
||||
;
|
||||
; Modifies:
|
||||
; All, except BP, DS, and flags.
|
||||
; Also, possible side effects of INT call.
|
||||
;
|
||||
; Exceptions:
|
||||
; INT 24H call may result from some INT 21H MS-DOS calls.
|
||||
;
|
||||
;******************************************************************************
|
||||
|
||||
.CODE
|
||||
|
||||
INTERRUPT PROC FAR
|
||||
|
||||
PUSH BP ;save BASCOM frame pointer on stack
|
||||
MOV BP,SP ;establish program frame reference
|
||||
ADD SP,FRM_SIZ ;allocate working space for frame
|
||||
MOV WORD PTR [BP].REG_NUM,08H ;eight regs used (not DS or ES)
|
||||
JMP SHORT INTERRUPT_COMMON ;jump to common code
|
||||
|
||||
INTERRUPT ENDP
|
||||
|
||||
|
||||
INTERRUPTX PROC FAR
|
||||
|
||||
PUSH BP ;save BASCOM frame pointer on stack
|
||||
MOV BP,SP ;establish program frame reference
|
||||
ADD SP,FRM_SIZ ;allocate working space for frame
|
||||
MOV WORD PTR [BP].REG_NUM,0AH ;ten regs used (including DS and ES)
|
||||
|
||||
; Save a copy of the processor flags, SI, DI, and DS in the stack frame.
|
||||
|
||||
INTERRUPT_COMMON:
|
||||
MOV [BP].OLD_SI,SI ;save old SI for interpreter
|
||||
MOV [BP].OLD_DI,DI ;save old DI for interpreter
|
||||
MOV [BP].UCODE_DS,DS;save DS for interpreter
|
||||
PUSHF ;push the flags on the stack
|
||||
POP [BP].UCODE_FLGS ;put value in the stack frame
|
||||
|
||||
; Move eight or ten words (depending if executing INTERRUPT or INTERRUPTX)
|
||||
; of the integer input array from the far pointer computed to the frame.
|
||||
|
||||
MOV SI,[BP].ARG2 ;and array offset - pointer in DS:SI
|
||||
LEA DI,[BP].INT_AX ;get start of temporary register storage.
|
||||
MOV CX,[BP].REG_NUM ;eight or ten words to move
|
||||
CLD ;movement is to higher memory
|
||||
PUSH SS
|
||||
POP ES
|
||||
REP MOVSW ;move the array into the stack frame
|
||||
|
||||
; Save stack frame pointer to recover its value after the INT call.
|
||||
|
||||
PUSH BP ;saved to first word past the stack frame
|
||||
|
||||
; Create a two-instruction program on the stack to execute the
|
||||
; INT call requested and return with stack cleanup.
|
||||
;
|
||||
; INT XX (hex: CD XX)
|
||||
; RETF 06 (hex: CA 06 00)
|
||||
;
|
||||
; In the case of INT 25 and 26 (which leave a word of flags on the stack)
|
||||
; We generate:
|
||||
;
|
||||
; INT XX (hex: CD XX)
|
||||
; ADD SP,2 (hex: 83 C4 02)
|
||||
; RETF 08 (hex: CA 08 00)
|
||||
;
|
||||
MOV SI,[BP].ARG1 ;[SI] = ptr to first CALL arg - interrupt #
|
||||
MOV BX,[SI] ;[BL] = get integer value of INT type
|
||||
OR BH,BH ;test if in range, 00 to FFH is legal
|
||||
JZ NO_INT_ERROR ;if not, then error - jump
|
||||
JMP INT_ERROR ;long jump to error routine
|
||||
NO_INT_ERROR:
|
||||
|
||||
CMP BL,25H ;Interrupt 25 request?
|
||||
JZ Int2526 ;Jump if so
|
||||
CMP BL,26H ;Interrupt 26 request?
|
||||
JNZ IntNorm ;Jump if other, "normal" interrupt
|
||||
Int2526:
|
||||
MOV AX,8 ;[AX] = argument of RETF instruction
|
||||
PUSH AX
|
||||
MOV AX,0CA02H ;[AX] = RETF opcode, & arg to ADD SP
|
||||
PUSH AX
|
||||
MOV AX,0C483H ;[AX] = ADD SP, opcode
|
||||
PUSH AX
|
||||
JMP SHORT IntInstruct
|
||||
|
||||
IntNorm:
|
||||
XOR AX,AX ;value of second word past frame
|
||||
PUSH AX ;put on stack - 00 byte of RETF and filler
|
||||
MOV AX,06CAH ;value of third word past frame
|
||||
PUSH AX ;put on stack - CA 06 bytes of RETF
|
||||
IntInstruct:
|
||||
MOV AH,BL ;move interrupt number to upper byte of AX
|
||||
MOV AL,0CDH ;value of fourth word past frame
|
||||
PUSH AX ;put on stack - CD XX bytes of INT XX
|
||||
|
||||
; Push far pointer of return address after the stack program
|
||||
; executes, which is INT_RET in this code segment.
|
||||
|
||||
PUSH CS ;push current code segment for return segment
|
||||
MOV AX,OFFSET INT_RET ;offset just after stack program call
|
||||
PUSH AX ;push value for return offset
|
||||
|
||||
; Push far pointer pointer to the start of the stack program.
|
||||
; The stack program will be entered by executing a RETF after the
|
||||
; registers are set up.
|
||||
|
||||
PUSH SS ;push current stack segment for starting ptr
|
||||
MOV AX,SP ;get current stack offset
|
||||
ADD AX,6 ;move past the last three stack entries
|
||||
PUSH AX ;push offset for starting ptr of stack program
|
||||
|
||||
; Move the input array values from the stack to their actual registers.
|
||||
|
||||
MOV AX,[BP].INT_FLGS ;get input flag register value
|
||||
AND AX,0000111111010101B ;mask out undefined 8086 flags
|
||||
PUSH AX ;push masked flag register value
|
||||
|
||||
MOV AX,[BP].INT_AX ;set up input AX value
|
||||
MOV BX,[BP].INT_BX ;set up input BX value
|
||||
MOV CX,[BP].INT_CX ;set up input CX value
|
||||
MOV DX,[BP].INT_DX ;set up input DX value
|
||||
|
||||
MOV SI,[BP].INT_SI ;set up input SI value
|
||||
MOV DI,[BP].INT_DI ;set up input DI value
|
||||
|
||||
; For DS and ES, leave in the compiler data segment values if:
|
||||
; executing INTERRUPT; or executing INTERRUPTX with array values of -1.
|
||||
|
||||
CMP WORD PTR [BP].REG_NUM,08H ;test if executing INTERRUPT
|
||||
JE INT_ES_DEF ;if so, then use both default values
|
||||
|
||||
CMP [BP].INT_DS,0FFFFH ;test if default DS to be used
|
||||
JE INT_DS_DEF ;if so, then leave it unchanged
|
||||
MOV DS,[BP].INT_DS ;set up input DS value
|
||||
INT_DS_DEF:
|
||||
CMP [BP].INT_ES,0FFFFH ;test if default ES to be used
|
||||
JE INT_ES_DEF ;if so, then leave it unchanged
|
||||
MOV ES,[BP].INT_ES ;set up input ES value
|
||||
INT_ES_DEF:
|
||||
|
||||
MOV BP,[BP].INT_BP ;set up input BP value
|
||||
;must be last move using BP
|
||||
|
||||
POPF ;set up input flag register value
|
||||
|
||||
; With all registers set according to the input array, execute the
|
||||
; stack program.
|
||||
;
|
||||
; The following RETF pops the last two stack entries, which are
|
||||
; interpreted as a far pointer to the stack program.
|
||||
;
|
||||
; The stack program executes the INT XX call which changes the
|
||||
; registers (flags included) to the values to be put into the
|
||||
; output array.
|
||||
;
|
||||
; The stack program then executes the RETF 06 instruction which
|
||||
; does two operations. First, the next two entries on stack are
|
||||
; popped and interpreted as a far ptr return address, which points
|
||||
; the code at INT_RET in this code segment. Second, the stack
|
||||
; pointer is then adjusted by six bytes to remove the six-byte
|
||||
; program from the stack.
|
||||
|
||||
RET ;far return to execute stack program, etc.
|
||||
INT_RET:
|
||||
|
||||
; The stack should now contain only the first entry past the
|
||||
; frame, the value of the stack frame pointer itself. First
|
||||
; save the BP value from the INT call, then get the old value
|
||||
; to reference the frame.
|
||||
|
||||
PUSH BP ;save post-INT value of BP
|
||||
MOV BP,SP ;temporary frame is second word past frame
|
||||
MOV BP,[BP+02H] ;get real frame reference value
|
||||
|
||||
; Put post-INT value of all registers into the frame variables
|
||||
; to be subsequently written into the output array.
|
||||
|
||||
PUSHF ;put flags on the stack
|
||||
POP [BP].INT_FLGS ;put in post-INT flag register value
|
||||
|
||||
PUSH [BP].UCODE_FLGS ;get old copy of flags from frame
|
||||
POPF ;and restore the old flag values
|
||||
|
||||
MOV [BP].INT_AX,AX ;put in post-INT AX value
|
||||
MOV [BP].INT_BX,BX ;put in post-INT BX value
|
||||
MOV [BP].INT_CX,CX ;put in post-INT CX value
|
||||
MOV [BP].INT_DX,DX ;put in post-INT DX value
|
||||
|
||||
MOV AX,[BP].INT_BP_TMP ;get post-INT BP value (one entry past frame)
|
||||
MOV [BP].INT_BP,AX ;put in post-INT BP value
|
||||
|
||||
MOV [BP].INT_SI,SI ;put in post-INT SI value
|
||||
MOV [BP].INT_DI,DI ;put in post-INT DI value
|
||||
|
||||
MOV [BP].INT_DS,DS ;put in post-INT DS value
|
||||
MOV [BP].INT_ES,ES ;put in post-INT ES value
|
||||
|
||||
; Move frame register values to the output array whose
|
||||
; far pointer is in the frame.
|
||||
|
||||
MOV DS,[BP].UCODE_DS;replace original DS value
|
||||
|
||||
LEA SI,[BP].INT_AX ;get start of register area in frame
|
||||
|
||||
PUSH DS
|
||||
POP ES
|
||||
MOV DI,[BP].ARG3 ;get output array offset
|
||||
MOV CX,[BP].REG_NUM ;eight or ten words to move
|
||||
CLD ;movement is toward upper memory
|
||||
REP MOVSW ;perform the transfer
|
||||
|
||||
; Clean up stack to remove frame. Remove CALL arguments with RETF.
|
||||
|
||||
MOV SI,[BP].OLD_SI ;replace old SI for interpreter
|
||||
MOV DI,[BP].OLD_DI ;replace old DI for interpreter
|
||||
MOV SP,BP ;deallocate temporary frame variables
|
||||
POP BP ;return compiler frame pointer
|
||||
RET 06 ;remove three CALL arguments and far return
|
||||
|
||||
; If error, then restore DS, set int_no to -1 to report error,
|
||||
; clean up, and exit.
|
||||
|
||||
INT_ERROR:
|
||||
MOV SI,[BP].ARG1 ;ptr to first CALL arg - interrupt number
|
||||
MOV [SI],0FFFFH ;set interrupt number to -1 for error
|
||||
MOV SI,[BP].OLD_SI ;replace old SI for interpreter
|
||||
MOV DI,[BP].OLD_DI ;replace old DI for interpreter
|
||||
MOV DS,[BP].UCODE_DS;replace original DS value
|
||||
MOV SP,BP ;deallocate temporary frame variables
|
||||
POP BP ;return compiler frame pointer
|
||||
RET 06 ;remove three CALL arguments and far return
|
||||
|
||||
INTERRUPTX ENDP
|
||||
|
||||
END
|
BIN
Microsoft QuickBASIC v4/LIB.EXE
Normal file
BIN
Microsoft QuickBASIC v4/LIB.EXE
Normal file
Binary file not shown.
BIN
Microsoft QuickBASIC v4/LINK.EXE
Normal file
BIN
Microsoft QuickBASIC v4/LINK.EXE
Normal file
Binary file not shown.
BIN
Microsoft QuickBASIC v4/MOUSE.COM
Normal file
BIN
Microsoft QuickBASIC v4/MOUSE.COM
Normal file
Binary file not shown.
BIN
Microsoft QuickBASIC v4/NOCOM.OBJ
Normal file
BIN
Microsoft QuickBASIC v4/NOCOM.OBJ
Normal file
Binary file not shown.
BIN
Microsoft QuickBASIC v4/NOEM.OBJ
Normal file
BIN
Microsoft QuickBASIC v4/NOEM.OBJ
Normal file
Binary file not shown.
267
Microsoft QuickBASIC v4/PACKING.LST
Normal file
267
Microsoft QuickBASIC v4/PACKING.LST
Normal file
@ -0,0 +1,267 @@
|
||||
"PACKING.LST" File
|
||||
Disk Contents for the MICROSOFT(R) QuickBASIC Compiler
|
||||
Version 4.0 for IBM(R) Personal Computers
|
||||
and Compatibles
|
||||
|
||||
(C) Copyright Microsoft Corporation, 1987
|
||||
|
||||
THIS FILE GIVES A COMPLETE LIST OF ALL FILES AND DIRECTORIES ON THE TWO
|
||||
DISTRIBUTION DISKS PROVIDED WITH THIS VERSION OF QUICKBASIC.
|
||||
|
||||
==< Contents of DISK 1: Program and Libraries Disk >=========================
|
||||
|
||||
FILE DESCRIPTION
|
||||
---- -----------------------------------------------------
|
||||
QB.EXE The Microsoft QuickBASIC program development
|
||||
environment.
|
||||
|
||||
QB.HLP A file containing information used by QuickBASIC's
|
||||
on-line Help. This file must be in the current
|
||||
directory -- or in a directory listed in the setting
|
||||
for your PATH environment variable -- if you want to
|
||||
use Help from within the QuickBASIC environment.
|
||||
|
||||
PACKING.LST A list of all files provided with QuickBASIC.
|
||||
|
||||
README.DOC Information that was unavailable when the QuickBASIC
|
||||
manuals were printed.
|
||||
|
||||
SETUP.BAT The first part of the QuickBASIC installation
|
||||
program (this batch file calls SETUP1.BAT). Run this
|
||||
batch file to install QuickBASIC on your hard-disk
|
||||
system.
|
||||
|
||||
SETUP1.BAT The second part of the QuickBASIC installation
|
||||
program.
|
||||
|
||||
BC.EXE The BASIC command-line compiler invoked by the Run
|
||||
menu's Make EXE File command or by the bc command
|
||||
from the DOS command line.
|
||||
|
||||
LIB.EXE The Microsoft Library Manager; used to create
|
||||
stand-alone (.LIB) libraries.
|
||||
|
||||
LINK.EXE The Microsoft Overlay Linker; used to create
|
||||
executable files and Quick libraries.
|
||||
|
||||
BRUN40.EXE The QuickBASIC run-time module; required for running
|
||||
executable files created with BRUN40.LIB.
|
||||
|
||||
BRUN40.LIB The QuickBASIC run-time-module library; used for
|
||||
creating executable files from QuickBASIC and DOS.
|
||||
|
||||
==< Contents of DISK 2: Utilities and Examples Disk >========================
|
||||
|
||||
---------------------------------------------------------------------------
|
||||
Important Notes
|
||||
---------------
|
||||
This disk contains a number of demonstration and utility programs written
|
||||
in BASIC. These files are for informational and recreational purposes
|
||||
only, and Microsoft makes no warranties, either expressed or implied,
|
||||
as to their suitability for specific purposes or their correctness,
|
||||
accuracy, or reliability. The entire risk as to the results and
|
||||
performance of the software is assumed by you.
|
||||
|
||||
All programs ending with the .BAS extension are QuickBASIC source files.
|
||||
Programs with an asterisk (*) next to their names require a color-graphics
|
||||
adapter to run.
|
||||
---------------------------------------------------------------------------
|
||||
|
||||
FILE OR DIRECTORY DESCRIPTION
|
||||
----------------- -----------------------------------------------------
|
||||
BCOM40.LIB The QuickBASIC alternate run-time-module library;
|
||||
used for creating executable files from QuickBASIC
|
||||
and DOS (files created with this library do not
|
||||
require BRUN40.EXE to run).
|
||||
|
||||
BQLB40.LIB The library of supporting routines that are used when
|
||||
creating Quick libraries.
|
||||
|
||||
MOUSE.COM The Mouse driver for use with QuickBASIC programs
|
||||
that call mouse functions.
|
||||
|
||||
QBHERC.COM The driver file for use with computers equipped with
|
||||
a Hercules(R) Graphics Card, Graphics Card Plus,
|
||||
Hercules InColor Card, or 100%-compatible clones of
|
||||
these graphics cards. This file allows you to write
|
||||
BASIC programs that use screen mode 3 for graphics
|
||||
output. (See the README.DOC file for more information.)
|
||||
|
||||
FIXSHIFT.COM A terminate-and-stay-resident program that fixes a bug
|
||||
in the ROM BIOS of some machines with keyboards that
|
||||
have an extra set of DIRECTION (i.e. arrow) keys, in
|
||||
addition to those on the numeric keypad. See README.DOC
|
||||
for more information, if you have such a keyboard.
|
||||
|
||||
QB.LIB The stand-alone library containing support routines
|
||||
for DOS system calls.
|
||||
|
||||
QB.QLB The Quick library containing support routines for
|
||||
DOS system calls.
|
||||
|
||||
QB.BI An include file for use with BASIC programs that
|
||||
call any of the following routines in the QB.QLB
|
||||
Quick library or in the QB.LIB stand-alone library:
|
||||
ABSOLUTE, INTERRUPT, INTERRUPTX, INT86OLD, or
|
||||
INT86XOLD. The QB.BI file defines the types for
|
||||
arguments passed to these routines and also gives
|
||||
DECLARE statements for these routines.
|
||||
|
||||
QB.PIF A file that provides information to aid in running
|
||||
QuickBASIC under Microsoft Windows.
|
||||
|
||||
ABSOLUTE.ASM The assembly-language source for the ABSOLUTE
|
||||
routine in QB.QLB and QB.LIB. This routine
|
||||
allows you to call a machine-language procedure
|
||||
from a BASIC program. (BASIC's CALL statement
|
||||
and the new DECLARE statement provide a simpler way
|
||||
to call other-language procedures from BASIC.)
|
||||
This source file is provided for reference only, and
|
||||
is not required to use the ABSOLUTE routine.
|
||||
|
||||
INTRPT.ASM The assembly-language source for the INTERRUPT and
|
||||
INTERRUPTX routines in the QB.QLB and QB.LIB
|
||||
libraries. These routines allow you to perform
|
||||
DOS system calls from a BASIC program. This source
|
||||
file is provided for reference only, and is not
|
||||
required to use the INTERRUPT or INTERRUPTX routines.
|
||||
|
||||
NOCOM.OBJ (NO COMmunication). An object file to link with BASIC
|
||||
programs that do not require communications support.
|
||||
Linking with NOCOM.OBJ reduces the size of executable
|
||||
files that do not perform any communications activity.
|
||||
|
||||
NOEM.OBJ (NO EMulation). An object file to link with BASIC
|
||||
programs that will always be run on machines with an
|
||||
8087 or 80287 math coprocessor chip. Linking with
|
||||
NOEM.OBJ turns off software emulation of the math
|
||||
chip's function, and reduces the size of the
|
||||
executable file.
|
||||
|
||||
DEMO1.BAS The BASICA version of the sound-effects demonstration
|
||||
program referred to in Chapter 2 of "Learning and
|
||||
Using Microsoft QuickBASIC."
|
||||
|
||||
DEMO2.BAS The QuickBASIC 2.0 version of the sound-effects
|
||||
demonstration program referred to in Chapter 2 of
|
||||
"Learning and Using Microsoft QuickBASIC."
|
||||
|
||||
DEMO3.BAS The QuickBASIC 4.0 version of the sound-effects
|
||||
demonstration program referred to in Chapter 2 of
|
||||
"Learning and Using Microsoft QuickBASIC."
|
||||
|
||||
REMLINE.BAS A utility program that converts BASICA programs
|
||||
saved in ASCII format to QuickBASIC-style programs
|
||||
by removing unreferenced line numbers.
|
||||
|
||||
SORTDEMO.BAS A program that uses multicolored bars and sound to
|
||||
illustrate various sorting algorithms.
|
||||
|
||||
TORUS.BAS* A graphics demonstration program that draws a
|
||||
multicolored doughnut-shaped figure on the screen,
|
||||
then makes it appear to rotate by shifting colors
|
||||
in the palette.
|
||||
|
||||
\SOURCE A directory containing BASIC programs printed in the
|
||||
QuickBASIC manuals, as well as other demonstration
|
||||
programs. See list of contents for this directory
|
||||
below.
|
||||
|
||||
==< Contents of \SOURCE directory on DISK 2 >================================
|
||||
|
||||
BALLPSET.BAS* A program that bounces a ball off the bottom and
|
||||
sides of the screen by using the PSET option with
|
||||
the graphics PUT statement.
|
||||
|
||||
BALLXOR.BAS* A program that bounces a ball off the bottom and
|
||||
sides of the screen by using the XOR option with
|
||||
the graphics PUT statement.
|
||||
|
||||
BAR.BAS* A program that turns input data into a bar chart.
|
||||
|
||||
CAL.BAS A program that prints a calendar for any month in
|
||||
any year from 1899 to 2099.
|
||||
|
||||
CHECK.BAS A checkbook-balancing program that sorts and prints a
|
||||
list of any deposits and withdrawals input by the
|
||||
user, then prints the final balance in the checking
|
||||
account.
|
||||
|
||||
COLORS.BAS* A program showing all combinations of the 16 background
|
||||
colors and 3 foreground colors (distinct from the
|
||||
background) in the 2 color palettes available in screen
|
||||
mode 1.
|
||||
|
||||
CRLF.BAS A program that opens an ASCII file, expands any lines
|
||||
ending with just a carriage return or a line feed to
|
||||
a carriage-return--line-feed combination, then writes
|
||||
the adjusted lines to a new file.
|
||||
|
||||
CUBE.BAS* A program that illustrates simple animation of a
|
||||
cube by using multiple screen pages in screen mode 7.
|
||||
|
||||
EDPAT.BAS* A program that allows you to edit a pattern tile
|
||||
for use in a PAINT statement. With pattern tiles,
|
||||
you can fill any enclosed graphics area on the screen
|
||||
with a pattern.
|
||||
|
||||
ENTAB.BAS A program that compresses an ASCII file by replacing
|
||||
runs of spaces with tab characters.
|
||||
|
||||
FILERR.BAS A program that searches for a string of characters in
|
||||
an ASCII file. This program traps and handles common
|
||||
file-access errors such as the user's entering an
|
||||
invalid file name or leaving a drive door open.
|
||||
|
||||
FLPT.BAS A program that lets you examine the internal format
|
||||
used by BASIC to store single-precision numbers.
|
||||
|
||||
HIDE.BAS A program that lets you hide or display a file, thus
|
||||
controlling whether or not it appears when you use
|
||||
the DIR command from DOS to list the contents of the
|
||||
directory containing the file.
|
||||
|
||||
INDEX.BAS A file I/O program that builds and searches an index
|
||||
of record numbers from a random-access data file.
|
||||
|
||||
MANDEL.BAS* A program that generates a fractal (a colorful graphic
|
||||
representation of the properties of certain real
|
||||
numbers) on the screen.
|
||||
|
||||
PALETTE.BAS* A program that demonstrates how to give the illusion
|
||||
of movement by rotating the colors displayed by
|
||||
the color attributes from 1 to 15.
|
||||
|
||||
PLOTTER.BAS* A simple line-sketching program that uses BASIC's
|
||||
DRAW statement.
|
||||
|
||||
QLBDUMP.BAS A program that allows you to get a listing of the
|
||||
PUBLIC code and data symbols in a QuickBASIC Quick
|
||||
library.
|
||||
|
||||
SEARCH.BAS A program that searches any disk file for a pattern
|
||||
and reports every byte position in the file where
|
||||
the pattern begins.
|
||||
|
||||
SINEWAVE.BAS* A program that plots the graph of the sine-wave
|
||||
function for angle values from 0 to PI (3.14159265)
|
||||
radians.
|
||||
|
||||
STRTONUM.BAS A program that converts to a numeric value any number
|
||||
input as a string, after first filtering invalid
|
||||
numeric characters (such as commas) out of the
|
||||
string.
|
||||
|
||||
TERMINAL.BAS A program that turns your computer into a "dumb"
|
||||
terminal when used with a modem.
|
||||
|
||||
TOKEN.BAS A program that breaks an input string into a series
|
||||
of tokens (a string of characters delimited by
|
||||
blank spaces, tabs, or punctuation marks such as
|
||||
commas or semicolons).
|
||||
|
||||
WHEREIS.BAS A program that recursively searches through all
|
||||
directories on a disk for the file name input by the
|
||||
user. When WHEREIS finds the file, it prints the
|
||||
complete directory path to the file.
|
||||
|
71
Microsoft QuickBASIC v4/QB.BI
Normal file
71
Microsoft QuickBASIC v4/QB.BI
Normal file
@ -0,0 +1,71 @@
|
||||
'***
|
||||
' QB.BI - Assembly Support Include File
|
||||
'
|
||||
' Copyright <C> 1987 Microsoft Corporation
|
||||
'
|
||||
' Purpose:
|
||||
' This include file defines the types and gives the DECLARE
|
||||
' statements for the assembly language routines ABSOLUTE,
|
||||
' INTERRUPT, INTERRUPTX, INT86OLD, and INT86XOLD.
|
||||
'
|
||||
'***************************************************************************
|
||||
'
|
||||
' Define the type needed for INTERRUPT
|
||||
'
|
||||
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
|
||||
'
|
||||
' Define the type needed for INTERUPTX
|
||||
'
|
||||
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
|
||||
'
|
||||
' DECLARE statements for the 5 routines
|
||||
' -------------------------------------
|
||||
'
|
||||
' Generate a software interrupt, loading all but the segment registers
|
||||
'
|
||||
DECLARE SUB INTERRUPT (intnum AS INTEGER,inreg AS RegType,outreg AS RegType)
|
||||
'
|
||||
' Generate a software interrupt, loading all registers
|
||||
'
|
||||
DECLARE SUB INTERRUPTX (intnum AS INTEGER,inreg AS RegTypeX, outreg AS RegTypeX)
|
||||
'
|
||||
' Call a routine at an absolute address.
|
||||
' NOTE: If the routine called takes parameters, then they will have to
|
||||
' be added to this declare statement before the parameter given.
|
||||
'
|
||||
DECLARE SUB ABSOLUTE (address AS INTEGER)
|
||||
'
|
||||
' Generate a software interrupt, loading all but the segment registers
|
||||
' (old version)
|
||||
'
|
||||
DECLARE SUB INT86OLD (intnum AS INTEGER,_
|
||||
inarray(1) AS INTEGER,_
|
||||
outarray(1) AS INTEGER)
|
||||
'
|
||||
' Gemerate a software interrupt, loading all the registers
|
||||
' (old version)
|
||||
'
|
||||
DECLARE SUB INT86XOLD (intnum AS INTEGER,_
|
||||
inarray(1) AS INTEGER,_
|
||||
outarray(1) AS INTEGER)
|
||||
'
|
BIN
Microsoft QuickBASIC v4/QB.EXE
Normal file
BIN
Microsoft QuickBASIC v4/QB.EXE
Normal file
Binary file not shown.
BIN
Microsoft QuickBASIC v4/QB.HLP
Normal file
BIN
Microsoft QuickBASIC v4/QB.HLP
Normal file
Binary file not shown.
BIN
Microsoft QuickBASIC v4/QB.LIB
Normal file
BIN
Microsoft QuickBASIC v4/QB.LIB
Normal file
Binary file not shown.
BIN
Microsoft QuickBASIC v4/QB.PIF
Normal file
BIN
Microsoft QuickBASIC v4/QB.PIF
Normal file
Binary file not shown.
BIN
Microsoft QuickBASIC v4/QB.QLB
Normal file
BIN
Microsoft QuickBASIC v4/QB.QLB
Normal file
Binary file not shown.
BIN
Microsoft QuickBASIC v4/QBHERC.COM
Normal file
BIN
Microsoft QuickBASIC v4/QBHERC.COM
Normal file
Binary file not shown.
407
Microsoft QuickBASIC v4/README.DOC
Normal file
407
Microsoft QuickBASIC v4/README.DOC
Normal file
@ -0,0 +1,407 @@
|
||||
"README.DOC" File
|
||||
Release Notes for MICROSOFT(R) QuickBASIC
|
||||
Version 4.0 for IBM(R) Personal Computers
|
||||
and Compatibles
|
||||
|
||||
(C) Copyright Microsoft Corporation, 1987
|
||||
|
||||
THIS FILE CONTAINS IMPORTANT INFORMATION CONCERNING VERSION 4.0 OF
|
||||
MICROSOFT(R) QuickBASIC. PLEASE READ THE ENTIRE FILE BEFORE USING
|
||||
QuickBASIC.
|
||||
|
||||
This file has seven parts:
|
||||
|
||||
PART CONTENTS
|
||||
|
||||
|
||||
1 Information about additions and changes to the
|
||||
Learning and Using Microsoft QuickBASIC manual.
|
||||
|
||||
2 Information about additions and changes to the
|
||||
BASIC Language Reference manual
|
||||
|
||||
3 Information about additions and changes to the
|
||||
Programming in BASIC: Selected Topics manual
|
||||
|
||||
4 Using your Mouse with QuickBASIC
|
||||
|
||||
5 Using QuickBASIC with 3.5-inch floppy disks
|
||||
|
||||
6 Supplementary information on mixed-language programming
|
||||
|
||||
7 Using Btrieve with QuickBASIC
|
||||
|
||||
===< Part 1: Changes for Learning and Using Microsoft QuickBASIC >===========
|
||||
|
||||
Page Correction
|
||||
---- ----------
|
||||
--- Some keyboards have an extra set of DIRECTION (i.e. arrow) keys, in
|
||||
addition to those on the numeric keypad. A bug in the ROM BIOS of
|
||||
some machines with these keyboards can interfere with the QuickBASIC
|
||||
editor. Disk 3 (disk 2, if you are using 3.5-inch disks) includes a
|
||||
program, FIXSHIFT.COM, that fixes this bug. If you have such a
|
||||
keyboard, run this program by typing FIXSHIFT. If your machine does
|
||||
not have the bug, FIXSHIFT displays a message telling you so.
|
||||
Otherwise FIXSHIFT prompts you for the appropriate actions. FIXSHIFT
|
||||
takes about 450 bytes of memory. Except for the BIOS bug, it has no
|
||||
effect on other programs you run.
|
||||
|
||||
--- QuickBASIC Version 4.0 supports Hercules (R) display adapters.
|
||||
See the entry for the SCREEN statement in Part 2, below.
|
||||
|
||||
xxii If you install an IBM (R) Personal System/2 (TM) Video Graphics
|
||||
Array display adapter (VGA) in a non-PS/2 machine, the VGA adapter
|
||||
should be the only adapter in the system, and you should not use
|
||||
mono modes (SCREEN 10) if you have a color monitor. Similarly, you
|
||||
should not use color modes (SCREEN 1, 2, 7, 8, 9, 11, 12, 13) if you
|
||||
have a monochrome monitor.
|
||||
|
||||
11 Suggestions for using QuickBASIC with a single-floppy system:
|
||||
|
||||
Disk 1
|
||||
======
|
||||
QB.EXE
|
||||
Your program source file
|
||||
(Optional: Operating system files)
|
||||
(Optional: QB.QLB)
|
||||
|
||||
Disk 2
|
||||
======
|
||||
BC.EXE
|
||||
LINK.EXE
|
||||
LIB.EXE
|
||||
BRUN40.EXE
|
||||
BRUN40.LIB
|
||||
|
||||
Disk 3
|
||||
======
|
||||
BCOM40.EXE
|
||||
|
||||
When you make executable files and Quick libraries from within the
|
||||
environment, you have to swap the disks in and out of your disk
|
||||
drive to make the proper programs and libraries available. When
|
||||
specific files cannot be found on the currently inserted disk,
|
||||
you will see the prompt "Cannot find file <filename>." Before you
|
||||
switch disks, type B: and press ENTER. (You can do this because,
|
||||
even though you do not have a physical drive B, DOS recognizes a
|
||||
logical drive B.) Insert the appropriate disk when prompted. Note
|
||||
that when the linker prompts for a path, you must also include the
|
||||
name of the file for which it is searching.
|
||||
|
||||
12 See Part 4 of this file for additional information on installing
|
||||
and using your Mouse with QuickBASIC.
|
||||
|
||||
-- There is a new option to LINK.EXE
|
||||
|
||||
Option: /NOE[XTDICTIONARY]
|
||||
|
||||
If the linker suspects that a public symbol has been redefined, it
|
||||
prompts you to link again with the /NOE option. When you do so, it
|
||||
searches the individual object files, rather than "dictionaries" it
|
||||
has created, to resolve conflicts. For example, when linking a
|
||||
program with NOEM.OBJ or NOCOM.OBJ, you must use the /NOE option.
|
||||
|
||||
-- NOEM.OBJ is a supplied object file. It allows stand-alone executable
|
||||
files compiled with the /O option to be substantially smaller when
|
||||
run on machines equipped with a math coprocessor (8087 or 80287).
|
||||
Note that programs linked with NOEM.OBJ do not run on machines that
|
||||
do not have a math coprocessor. If all your stand-alone executable
|
||||
files are always run on machines with coprocessors, you can use the
|
||||
following method to change the library that contains floating-point
|
||||
emulation routines (BCOM40.LIB) to produce smaller executable files:
|
||||
|
||||
LIB BCOM40.LIB -QB4EM.OBJ+NOEM.OBJ;
|
||||
|
||||
This command replaces the emulator math support in the stand-alone
|
||||
run-time library with support specific to the coprocessor.
|
||||
|
||||
Alternatively, you can explicitly link NOEM.OBJ from the command
|
||||
line on a case-by-case basis. For example, to create PROG.EXE
|
||||
using NOEM.OBJ, compile PROG.BAS with the /O option (either from
|
||||
within QuickBASIC or from the command line), then link as follows:
|
||||
|
||||
LINK PROG.OBJ+NOEM.OBJ/NOE;
|
||||
|
||||
245 PTR86 is no longer supported. Use VARSEG and VARPTR instead.
|
||||
Also, when used with a communications device LOF now returns the
|
||||
amount of space remaining (in bytes) in the output buffer. In
|
||||
previous versions this was returned in the input buffer. Also, note
|
||||
that a variable and SUB procedure could have the same name in previous
|
||||
versions. In Version 4.0, this causes a "duplicate definition" error.
|
||||
|
||||
===< Part 2: Changes for BASIC Language Reference >==========================
|
||||
|
||||
Page Correction
|
||||
---- ----------
|
||||
18 The program FLPT.BAS, as printed in the manual, produces a run-time
|
||||
error. The program has been corrected in the on-disk version.
|
||||
See the \SOURCE directory on disk 3 (or disk 2 if you are using
|
||||
3.5 inch disks).
|
||||
|
||||
84 The description of CALL ABSOLUTE says the file ABSOLUTE.OBJ must be
|
||||
linked with the program. This file is no longer supplied. Link with
|
||||
QB.LIB instead.
|
||||
|
||||
122 String concatenation is not permitted in a CONST statement.
|
||||
|
||||
373 The SCREEN statement now includes mode 3 for Hercules display
|
||||
adapters. The following is a brief summary of screen mode 3.
|
||||
See your Hercules documentation for details.
|
||||
|
||||
- QuickBASIC supports Hercules Graphics Card, Graphics
|
||||
Card Plus, InColor Card, and 100% compatibles
|
||||
|
||||
- You must use a monochrome monitor
|
||||
|
||||
- Hercules text mode is SCREEN 0; Hercules Graphics mode
|
||||
is SCREEN 3.
|
||||
|
||||
- You must load the Hercules driver (QBHERC.COM) before running
|
||||
your program. If the driver is not loaded, SCREEN 3 statement
|
||||
gives an "Illegal function call" error message. Type QBHERC
|
||||
to load the driver.
|
||||
|
||||
- Text dimensions are 80x25 (9x14 character box); bottom
|
||||
2 scan lines of 25th row are not visible.
|
||||
|
||||
- Resolution is 720x348 pixels, monochrome.
|
||||
|
||||
- Number of screen pages supported is 2.
|
||||
|
||||
- The PALETTE statement is not supported.
|
||||
|
||||
- In order to use the Mouse, you must follow special
|
||||
instructions for Hercules cards in the Microsoft Mouse
|
||||
Programmer's Reference Guide. (This must be ordered
|
||||
separately; it is not supplied with either the QuickBASIC
|
||||
or the Mouse package.)
|
||||
|
||||
477 - The "Advanced feature unavailable" error message may occur
|
||||
if you are using DOS Version 2.1 when trying to use a fea-
|
||||
ture supported only in later versions (i.e. file locking).
|
||||
|
||||
484 - The "Duplicate definition" error message also occurs if you
|
||||
have a SUB or FUNCTION procedure with the same name as a
|
||||
variable. In previous versions, this did not cause an error.
|
||||
|
||||
513 - Message 2024 ("Name : symbol multiply defined, use /NOE")
|
||||
should be numbered 2044
|
||||
|
||||
--------< New or Revised Error Messages >--------------------------------
|
||||
|
||||
Error Number Explanation
|
||||
------------ -----------
|
||||
|
||||
L1003 New message: "/QUICKLIB, /EXEPACK incompatible"
|
||||
You specified both options, /QUICKLIB and /EXEPACK, but
|
||||
these two options cannot be used together.
|
||||
|
||||
L2024 Message should read: "<name> : symbol already defined"
|
||||
Explanation: The linker has found a public-symbol
|
||||
redefinition. Remove extra definition(s).
|
||||
|
||||
L2043 Message should read: "Quick library support module missing"
|
||||
You did not specify, or LINK could not find, the object
|
||||
module or library required for creating a Quick library.
|
||||
In the case of QuickBASIC, the library provided is BQLB40.LIB
|
||||
|
||||
L4003 This message should be deleted from documentation.
|
||||
|
||||
U4157 LIB warning message: "Insufficient memory, extended
|
||||
dictionary not created."
|
||||
|
||||
U4158 LIB warning message: "Internal error, extended dictionary
|
||||
not created."
|
||||
Both of these LIB warnings just indicate that LIB was unable
|
||||
to create the extended dictionary. The library is still
|
||||
valid, but the linker cannot take advantage of extended
|
||||
dictionaries to link faster.
|
||||
|
||||
===< Part 3: Changes for Programming in BASIC: Selected Topics >============
|
||||
|
||||
141 In the "Information Returned" column for the LOC function, the
|
||||
description should read: "The amount of space remaining (in
|
||||
bytes) in the output buffer". (Note that this is a change from
|
||||
the behavior of LOF in previous versions of QuickBASIC).
|
||||
|
||||
===< Part 4: Using your Mouse with QuickBASIC >=============================
|
||||
|
||||
--------< New Mouse Driver for Use with QuickBASIC >------------------------
|
||||
|
||||
QuickBASIC Version 4.0 can be used with any mouse that is 100%
|
||||
compatible with the Microsoft Mouse. However, you must use a
|
||||
Microsoft Mouse driver Version 6.00 or later. Earlier versions may
|
||||
cause unpredictable behavior when used with QuickBASIC. MOUSE.COM,
|
||||
Version 6.11 is supplied with QuickBASIC Version 4.0.
|
||||
|
||||
Especially if you are writing programs that use the mouse, you
|
||||
should use the supplied version of the mouse driver when working in
|
||||
QuickBASIC. Previous versions have included MOUSE.SYS, which is
|
||||
installed by including the line DEVICE=MOUSE.SYS in your CONFIG.SYS
|
||||
file. This version of QuickBASIC includes MOUSE.COM, which is not
|
||||
installed via CONFIG.SYS. To install MOUSE.COM, just type MOUSE at
|
||||
the DOS prompt. To include MOUSE.COM automatically when your machine
|
||||
boots, make sure MOUSE.COM is in your search path, then put the line
|
||||
|
||||
MOUSE
|
||||
|
||||
in your AUTOEXEC.BAT file. To free up memory, you can remove the
|
||||
mouse driver at any time by typing MOUSE OFF at the DOS prompt.
|
||||
This will restore between 9K and 10.5K of memory with Version 6.11.
|
||||
|
||||
--------< Using Mouse Function Calls from QuickBASIC Programs >------------
|
||||
|
||||
If you are programming for the Microsoft Mouse, you should obtain
|
||||
the Microsoft Mouse Programmer's Reference Guide and the library
|
||||
MOUSE.LIB that comes with it. (These are not included in QuickBASIC
|
||||
or Mouse package and must be ordered separately). Most of the
|
||||
information in the Mouse programmer's reference guide applies
|
||||
directly to QuickBASIC Version 4. However, the following additional
|
||||
restrictions must be observed:
|
||||
|
||||
Certain Mouse function calls (Functions 9 & 16) require you to set
|
||||
up an integer array and pass the address of the array to the mouse
|
||||
driver. For previous versions, the only restriction on this array
|
||||
was that it had to be $STATIC (the default array type). In QuickBASIC
|
||||
Version 4.0, however, the array also must be in a COMMON block if you
|
||||
will be making the Mouse function call from within the QuickBASIC
|
||||
environment. In addition, it is recommended that the support code
|
||||
for the Mouse call be in a Quick library or linked into the
|
||||
executable file when making Mouse function calls from QuickBASIC.
|
||||
|
||||
To produce a Quick library for using Mouse function calls from
|
||||
within the QuickBASIC environment, use the following command line
|
||||
(produces MOUSE.QLB):
|
||||
|
||||
LINK MOUSE.LIB/QU,MOUSE.QLB,,BQLB40.LIB/NOE;
|
||||
|
||||
An example from PIANO.BAS (included with the Microsoft Mouse
|
||||
Programmer's Reference) for using Mouse function call 9:
|
||||
DEFINT A-Z
|
||||
DECLARE SUB MOUSE (M1, M2, M3, M4)
|
||||
DIM Cursor(15, 1)
|
||||
COMMON Cursor() ' ensures array data is in DGROUP
|
||||
.
|
||||
. (set up Cursor() for mouse cursor shape desired)
|
||||
.
|
||||
M1 = 9: M2 = 6: M3 = 0
|
||||
CALL MOUSE(M1, M2, M3, VARPTR(Cursor(0, 0)))
|
||||
|
||||
In addition to the above, note that Mouse function calls 21-23
|
||||
require dynamically allocated storage out of the home data segment.
|
||||
The recommended way to do this is to allocate space in a dynamic
|
||||
string variable based on the return value from function call 21,
|
||||
using the STRING$ or SPACE$ function, and using VARPTR on this
|
||||
string variable just prior to calling Mouse function call 22 or 23.
|
||||
|
||||
===< Part 5: Using QuickBASIC with 3.5-inch Floppy Disks >=============
|
||||
|
||||
If you have two 3.5-inch floppy-disk drives
|
||||
|
||||
Copy the files from the distribution disks to three other disks,
|
||||
as follows:
|
||||
|
||||
Disk 1: All files from distribution disk 1, plus all BRUN40
|
||||
and BQLB files appearing on distribution disk 2
|
||||
|
||||
Disk 2: BCOM40.LIB, BC.EXE, LINK.EXE, LIB.EXE
|
||||
|
||||
Disk 3: BASIC source files, Quick libraries, and QB.QLB
|
||||
|
||||
Most of the time you can just use disks 1 and 3, with disk 1 in
|
||||
drive A and disk 3 in drive B. When you make a Quick library or
|
||||
an executable file to run from DOS, you will see the prompt:
|
||||
|
||||
Cannot find file <filename>
|
||||
|
||||
Insert disk 2 in drive A and press ENTER. If the program requires
|
||||
a Quick library, make sure both the Quick library and the corresond-
|
||||
ing stand-alone (.LIB) library are on the disk in drive B.
|
||||
|
||||
If you have only a single 3.5-inch floppy disk drive
|
||||
|
||||
Prepare disks 1, 2, and 3 as with a 2-drive system. However, when
|
||||
you see the prompt "Cannot find file <filename>", type B: and press
|
||||
ENTER before inserting the proper disk. (You can do this because,
|
||||
even though you do not have a physical drive B, DOS recognizes a
|
||||
logical drive B.) Insert the appropriate disk when prompted. Note
|
||||
that when the linker prompts for a path, you must also include the
|
||||
name of the file for which it is searching.
|
||||
|
||||
===< Part 6: Supplementary Information on Mixed-Language Programming >======
|
||||
|
||||
--------< Linking from within QuickC or with QCL >--------------------------
|
||||
|
||||
Microsoft QuickC and the QCL command both set the /NOI linker
|
||||
by default. Therefore, you should not link from within QuickC, or
|
||||
with QCL, when your program contains modules written in a case-
|
||||
insensitive language such as BASIC. Use LINK to link your program
|
||||
from the command line.
|
||||
|
||||
--------< Pascal and Fortran Modules in QuickBASIC Programs >---------------
|
||||
|
||||
Modules compiled with Microsoft Pascal or Fortran can be linked with
|
||||
BASIC programs, as described in the Microsoft Mixed-Language
|
||||
Programming Guide. They can also be incorporated in Quick libraries.
|
||||
However, QuickBASIC programs containing code compiled with Microsoft
|
||||
Pascal must allocate at least 2K near-heap space for Pascal. This can
|
||||
be done by using the DIM statement to allocate a static array of 2K or
|
||||
greater in the NMALLOC named common block, for example, as follows:
|
||||
|
||||
DIM name%(2048)
|
||||
COMMON SHARED /NMALLOC/ name%()
|
||||
|
||||
The Pascal runtime assumes it always has at least 2K of near-heap
|
||||
space available. If the Pascal code cannot allocate the required
|
||||
space, QuickBASIC may crash. This applies to Pascal code in Quick
|
||||
libraries as well as Pascal code linked into executable files. The
|
||||
situation is similar for Fortran I/O, which also requires near
|
||||
buffer space, and which can be provided by the same means as the
|
||||
Pascal near malloc space.
|
||||
|
||||
--------< STATIC Array Allocation >---------------------------------------
|
||||
|
||||
If you are writing assembly-language modules for use in QuickBASIC
|
||||
programs, see Section 2.3.3, "Variable Storage Allocation," in the
|
||||
BASIC Language Reference. Assembly-language code should not assume
|
||||
data is in a particular segment. To avoid problems, pass data using
|
||||
the SEG or CALLS keywords, or use FAR pointers. Alternatively, you
|
||||
can declare all arrays dynamic (still using far pointers) since
|
||||
dynamic arrays are handled identically by BC and within QuickBASIC.
|
||||
|
||||
--------< Quick Libraries with Leading Zeros in the First Code Segment >--
|
||||
|
||||
A Quick library containing leading zeros in the first CODE segment
|
||||
is invalid, causing the message "Error in loading file <name> -
|
||||
Invalid format" when you try to load it in QuickBASIC. For example,
|
||||
this can occur if an assembly-language routine puts data that is
|
||||
initialized to zero in the first CODE segment, and it is subsequently
|
||||
listed first on the LINK command line when you make a Quick library.
|
||||
If you have this problem, do either of the following:
|
||||
(1) link with a BASIC module first on the LINK command line, or
|
||||
(2) make sure that, in whatever module comes first on the LINK
|
||||
command line, the first code segment starts with a non-zero byte.
|
||||
|
||||
===< Part 7: Using Btrieve with QuickBASIC >=========================
|
||||
|
||||
If you use Btrieve with QuickBASIC, you must make a small change to
|
||||
your programs for QuickBASIC Version 4.0. Currently your programs
|
||||
contain a statement that obtains the address of the field buffer for
|
||||
an open file. For example:
|
||||
|
||||
OPEN "NUL" AS #1
|
||||
FIELD #1, 20 AS CITY$, 10 AS STATE$
|
||||
FCB.ADDR% = VARPTR(#1) 'This statement obtains
|
||||
the address
|
||||
|
||||
In QuickBASIC Version 4.0, you should change the indicated statement
|
||||
to return the address of the first variable in your field buffer
|
||||
minus a constant, as follows:
|
||||
|
||||
OPEN "NUL" AS #1
|
||||
FIELD #1, 20 AS CITY$, 10 AS STATE$
|
||||
FCB.ADDR% = SADD(CITY$) - 188 'CITY$ is the first field
|
||||
buffer variable
|
||||
|
||||
Your programs should function correctly with Btrieve with this change.
|
||||
|
BIN
Microsoft QuickBASIC v4/REMLINE.BAS
Normal file
BIN
Microsoft QuickBASIC v4/REMLINE.BAS
Normal file
Binary file not shown.
34
Microsoft QuickBASIC v4/SETUP.BAT
Normal file
34
Microsoft QuickBASIC v4/SETUP.BAT
Normal file
@ -0,0 +1,34 @@
|
||||
ECHO OFF
|
||||
IF "%1" == "" GOTO UsageExit
|
||||
IF "%2" == "" GOTO UsageExit
|
||||
%1
|
||||
IF EXIST %2\*.* GOTO DoSetup
|
||||
md %2
|
||||
:DoSetup
|
||||
cd %2
|
||||
copy a:setup1.bat
|
||||
setup1 %1 %2 %3 %4
|
||||
|
||||
:UsageExit
|
||||
CLS
|
||||
ECHO Usage: A:SETUP drive workDir [exeDir [libDir] ]
|
||||
ECHO ÿ
|
||||
ECHO Where
|
||||
ECHO drive is the drive on which QuickBASIC is to be
|
||||
ECHO installed (ex: C:)
|
||||
ECHO workDir is the pathname to where you want your
|
||||
ECHO QuickBASIC source programs to go (ex: \QB4)
|
||||
ECHO exeDir is the pathname to where you want the
|
||||
ECHO executeable files to go (ex: \BIN)
|
||||
ECHO libDir is the pathname to where you want the
|
||||
ECHO library files to go (ex: \LIB)
|
||||
ECHO ÿ
|
||||
ECHO Examples: a:setup c: \qb4 \bin \lib
|
||||
ECHO a:setup c: \qb4 (copies ALL files to c:\qb4)
|
||||
ECHO ÿ
|
||||
ECHO Note: This setup batch file is intended only for assisting you
|
||||
ECHO in installing QuickBASIC onto your hard disk. Its use is
|
||||
ECHO optional; you can just copy all the files to the directory(s)
|
||||
ECHO of your choice, if you wish. If you do not have a hard disk,
|
||||
ECHO see the section entitled 'Installing QuickBASIC: Floppy-Disk
|
||||
ECHO Setup' in the 'Learning and Using QuickBASIC' manual.
|
84
Microsoft QuickBASIC v4/SETUP1.BAT
Normal file
84
Microsoft QuickBASIC v4/SETUP1.BAT
Normal file
@ -0,0 +1,84 @@
|
||||
ECHO OFF
|
||||
CLS
|
||||
ECHO ÿ
|
||||
ECHO Note that you need almost 1 MegaByte free on your hard disk; if you have
|
||||
ECHO less than a MegaByte, abort and copy just those files you really need.
|
||||
ECHO ÿ
|
||||
ECHO Type Ctrl-Break to abort if you don't have a hard disk or would rather
|
||||
ECHO just do it yourself - - -
|
||||
ECHO ÿ
|
||||
PAUSE
|
||||
IF "%3" == "" GOTO ExeNoDir
|
||||
IF EXIST %3\*.* GOTO GotExeDir
|
||||
md %3
|
||||
:GotExeDir
|
||||
ECHO Now copying BC.EXE, BRUN40.EXE, QB.EXE, LIB.EXE and LINK.EXE to %1%3
|
||||
copy a:*.exe %3
|
||||
GOTO CopyLib
|
||||
:ExeNoDir
|
||||
ECHO Now copying BC.EXE, BRUN40.EXE, QB.EXE, LIB.EXE and LINK.EXE to %1%2
|
||||
copy a:*.exe %2
|
||||
:CopyLib
|
||||
ECHO Now copying QB.HLP to %1%2
|
||||
copy a:qb.hlp %2
|
||||
IF "%4" == "" GOTO LibNoDir
|
||||
IF EXIST %4\*.* GOTO GotLibDir
|
||||
md %4
|
||||
:GotLibDir
|
||||
ECHO Now copying BRUN40.LIB to %1%4
|
||||
copy a:brun40.lib %4
|
||||
GOTO CopyOther
|
||||
:LibNoDir
|
||||
ECHO Now copying BRUN40.LIB to %1%2
|
||||
copy a:brun40.lib %2
|
||||
:CopyOther
|
||||
ECHO ÿ
|
||||
ECHO Put Disk 2 in drive A:
|
||||
PAUSE
|
||||
ECHO ÿ
|
||||
IF "%4" == "" GOTO Lib2NoDir
|
||||
IF EXIST %4\*.* GOTO Got2LibDir
|
||||
md %4
|
||||
:Got2LibDir
|
||||
ECHO Now copying BCOM40.LIB and BQLB40.LIB to %1%4
|
||||
copy a:b*.lib %4
|
||||
GOTO CopyRest
|
||||
:Lib2NoDir
|
||||
ECHO Now copying BCOM40.LIB and BQLB40.LIB to %1%2
|
||||
copy a:b*.lib %2
|
||||
:CopyRest
|
||||
ECHO ÿ
|
||||
IF "%3" == "" GOTO Exe2NoDir
|
||||
ECHO Now copying MOUSE.COM to %1%3
|
||||
copy a:mouse.com %3
|
||||
GOTO FinishUp
|
||||
:Exe2NoDir
|
||||
ECHO Now copying MOUSE.COM to %1%2
|
||||
copy a:mouse.com %2
|
||||
:FinishUp
|
||||
ECHO ÿ
|
||||
ECHO Now copying BAS files to %1%2
|
||||
copy a:*.bas %2
|
||||
copy a:\source\*.* %2
|
||||
ECHO ÿ
|
||||
ECHO Now copying other supporting files to %1%2
|
||||
copy a:qb.* %2
|
||||
copy a:*.obj %2
|
||||
ECHO ÿ
|
||||
ECHO Installation complete.
|
||||
ECHO ÿ
|
||||
ECHO Installation does NOT include modifying DOS environment variables.
|
||||
IF "%3" == "" GOTO Exe3NoDir
|
||||
ECHO Since you specified %1%3 for EXE and COM files, you should ensure
|
||||
ECHO you have an appropriate PATH= parameter in your autoexec.bat.
|
||||
:Exe3NoDir
|
||||
IF "%4" == "" GOTO Lib3NoDir
|
||||
ECHO Since you specified %1%4 for LIB files, you should ensure you have an
|
||||
ECHO appropriate LIB= parameter in your autoexec.bat.
|
||||
:Lib3NoDir
|
||||
ECHO For complete information on setting DOS environment variables for use
|
||||
ECHO with QuickBASIC, see the section entitled 'Setting DOS Environment
|
||||
ECHO Variables' in the 'Learning and Using QuickBASIC' manual.
|
||||
ECHO ÿ
|
||||
ECHO Note that installation does not copy README.DOC or PACKING.LST from disk 1
|
||||
ECHO nor QBHERC.COM, FIXSHIFT.COM, ABSOLUTE.ASM or INTRPT.ASM from disk 2.
|
20
Microsoft QuickBASIC v4/SIEVE.BAS
Normal file
20
Microsoft QuickBASIC v4/SIEVE.BAS
Normal file
@ -0,0 +1,20 @@
|
||||
1 SIZE% = 8190
|
||||
2 DIM FLAGS%(8191)
|
||||
3 PRINT "10 iterations"
|
||||
4 FOR X% = 1 TO 10
|
||||
5 COUNT% = 0
|
||||
6 FOR I% = 0 TO SIZE%
|
||||
7 FLAGS%(I%) = 1
|
||||
8 NEXT I%
|
||||
9 FOR I% = 0 TO SIZE%
|
||||
10 IF FLAGS%(I%) = 0 THEN 18
|
||||
11 PRIME% = I% + I% + 3
|
||||
12 K% = I% + PRIME%
|
||||
13 IF K% > SIZE% THEN 17
|
||||
14 FLAGS%(K%) = 0
|
||||
15 K% = K% + PRIME%
|
||||
16 GOTO 13
|
||||
17 COUNT% = COUNT% + 1
|
||||
18 NEXT I%
|
||||
19 NEXT X%
|
||||
20 PRINT COUNT%," PRIMES"
|
BIN
Microsoft QuickBASIC v4/SORTDEMO.BAS
Normal file
BIN
Microsoft QuickBASIC v4/SORTDEMO.BAS
Normal file
Binary file not shown.
BIN
Microsoft QuickBASIC v4/TORUS.BAS
Normal file
BIN
Microsoft QuickBASIC v4/TORUS.BAS
Normal file
Binary file not shown.
121
Microsoft QuickBASIC v4/TTT.BAS
Normal file
121
Microsoft QuickBASIC v4/TTT.BAS
Normal file
@ -0,0 +1,121 @@
|
||||
1 REM Tic Tac Toe solving app that learns what WOPR learned: you can't win
|
||||
2 REM Only three starting positions are examined. Others are just reflections of these
|
||||
3 REM b% -- The board
|
||||
4 REM al% -- Alpha, for pruning
|
||||
5 REM be% -- Beta, for pruning
|
||||
6 REM l% -- Top-level loop iteration
|
||||
7 REM wi% -- The winning piece (0 none, 1 X, 2, O )
|
||||
8 REM re% -- Resulting score of 4000/minmax board position. 5 draw, 6 X win, 4 Y win
|
||||
9 REM sx% -- Stack array for "recursion" X can be P, V, A, or B for those variables.
|
||||
10 REM v% -- Value of a board position
|
||||
11 REM st% -- Stack Pointer. Even for alpha/beta pruning Minimize plys, Odd for Maximize
|
||||
12 REM p% -- Current position where a new piece is played
|
||||
14 REM rw% -- Row in the Winner function (2000)
|
||||
15 REM cw% -- Column in the Winner function (2000)
|
||||
18 REM mc% -- Move count total for debugging. Should be a multiple of 6493
|
||||
19 REM Note: Can't use real recursion with GOSUB because stack is limited to roughly 5 deep
|
||||
20 REM BASIC doesn't support goto/gosub using arrays for target line numbers
|
||||
23 li% = val( command$ )
|
||||
24 if 0 = li% then li% = 1
|
||||
30 DIM b%(9)
|
||||
32 DIM sp%(10)
|
||||
34 DIM sv%(10)
|
||||
36 DIM sa%(10)
|
||||
37 DIM sb%(10)
|
||||
38 mc% = 0
|
||||
39 PRINT "start time: "; TIME$
|
||||
40 FOR l% = 1 TO li%
|
||||
41 mc% = 0
|
||||
42 al% = 2
|
||||
43 be% = 9
|
||||
44 b%(0) = 1
|
||||
45 GOSUB 4000
|
||||
58 al% = 2
|
||||
59 be% = 9
|
||||
60 b%(0) = 0
|
||||
61 b%(1) = 1
|
||||
62 GOSUB 4000
|
||||
68 al% = 2
|
||||
69 be% = 9
|
||||
70 b%(1) = 0
|
||||
71 b%(4) = 1
|
||||
72 GOSUB 4000
|
||||
73 b%(4) = 0
|
||||
74 REM print "mc: "; mc%; " l is "; l%
|
||||
80 NEXT l%
|
||||
82 REM print elap$
|
||||
83 PRINT "end time: "; TIME$
|
||||
84 print "iterations: "; li%
|
||||
85 PRINT "final move count "; mc%
|
||||
88 SYSTEM
|
||||
100 END
|
||||
|
||||
2000 wi% = b%(0)
|
||||
2010 IF 0 = wi% GOTO 2100
|
||||
2020 IF wi% = b%(1) AND wi% = b%(2) THEN RETURN
|
||||
2030 IF wi% = b%(3) AND wi% = b%(6) THEN RETURN
|
||||
2100 wi% = b%(3)
|
||||
2110 IF 0 = wi% GOTO 2200
|
||||
2120 IF wi% = b%(4) AND wi% = b%(5) THEN RETURN
|
||||
2200 wi% = b%(6)
|
||||
2210 IF 0 = wi% GOTO 2300
|
||||
2220 IF wi% = b%(7) AND wi% = b%(8) THEN RETURN
|
||||
2300 wi% = b%(1)
|
||||
2310 IF 0 = wi% GOTO 2400
|
||||
2320 IF wi% = b%(4) AND wi% = b%(7) THEN RETURN
|
||||
2400 wi% = b%(2)
|
||||
2410 IF 0 = wi% GOTO 2500
|
||||
2420 IF wi% = b%(5) AND wi% = b%(8) THEN RETURN
|
||||
2500 wi% = b%(4)
|
||||
2510 IF 0 = wi% THEN RETURN
|
||||
2520 IF wi% = b%(0) AND wi% = b%(8) THEN RETURN
|
||||
2530 IF wi% = b%(2) AND wi% = b%(6) THEN RETURN
|
||||
2540 wi% = 0
|
||||
2550 RETURN
|
||||
|
||||
4000 REM minmax function to find score of a board position
|
||||
4010 REM recursion is simulated with gotos
|
||||
4030 st% = 0
|
||||
4040 v% = 0
|
||||
4060 re% = 0
|
||||
4100 mc% = mc% + 1
|
||||
4102 REM gosub 3000
|
||||
4104 IF st% < 4 THEN GOTO 4150
|
||||
4105 GOSUB 2000
|
||||
4106 IF 0 = wi% THEN GOTO 4140
|
||||
4110 IF wi% = 1 THEN re% = 6: GOTO 4280
|
||||
4115 re% = 4
|
||||
4116 GOTO 4280
|
||||
4140 IF st% = 8 THEN re% = 5: GOTO 4280
|
||||
4150 IF st% AND 1 THEN v% = 2 ELSE v% = 9
|
||||
4160 p% = 0
|
||||
4180 IF 0 <> b%(p%) THEN GOTO 4500
|
||||
4200 IF st% AND 1 THEN b%(p%) = 1 ELSE b%(p%) = 2
|
||||
4210 sp%(st%) = p%
|
||||
4230 sv%(st%) = v%
|
||||
4245 sa%(st%) = al%
|
||||
4246 sb%(st%) = be%
|
||||
4260 st% = st% + 1
|
||||
4270 GOTO 4100
|
||||
4280 st% = st% - 1
|
||||
4290 p% = sp%(st%)
|
||||
4310 v% = sv%(st%)
|
||||
4325 al% = sa%(st%)
|
||||
4326 be% = sb%(st%)
|
||||
4328 b%(p%) = 0
|
||||
4330 IF st% AND 1 THEN GOTO 4340
|
||||
4331 IF re% = 4 THEN GOTO 4530
|
||||
4332 IF re% < v% THEN v% = re%
|
||||
4334 IF v% < be% THEN be% = v%
|
||||
4336 IF be% <= al% THEN GOTO 4520
|
||||
4338 GOTO 4500
|
||||
4340 IF re% = 6 THEN GOTO 4530
|
||||
4341 IF re% > v% THEN v% = re%
|
||||
4342 IF v% > al% THEN al% = v%
|
||||
4344 IF al% >= be% THEN GOTO 4520
|
||||
4500 p% = p% + 1
|
||||
4505 IF p% < 9 THEN GOTO 4180
|
||||
4520 re% = v%
|
||||
4530 IF st% = 0 THEN RETURN
|
||||
4540 GOTO 4280
|
||||
|
3
Microsoft QuickBASIC v4/m.bat
Normal file
3
Microsoft QuickBASIC v4/m.bat
Normal file
@ -0,0 +1,3 @@
|
||||
ntvdm -r:. -c bc %1.bas %1.obj %1.lst /O
|
||||
ntvdm -r:. -c link %1,,%1,.\,nul.def
|
||||
|
Loading…
Reference in New Issue
Block a user