quick basic v3

This commit is contained in:
davidly 2024-07-01 13:00:14 -07:00
parent 3af5efd0da
commit ea56ec6526
294 changed files with 16016 additions and 0 deletions

View File

@ -0,0 +1,30 @@
TITLE ABSOLUTE - helper for assembly routines
;***
; ABSOLUTE - Helper for calling BASIC interpreter assembly routines
;
; Just used to clear information from the stack to various registers and
; memory locations.
;***
CODE SEGMENT BYTE PUBLIC 'CODE'
ASSUME CS:CODE
PUBLIC ABSOLUTE
ABSOLUTE PROC FAR
POP DI ;return offset
POP SI ;return segment
POP BX ;address of routine offset
PUSH SI ;restack return segment
PUSH DI ;restack return offset
PUSH DS:[0] ;stack DEF SEG segment
PUSH [BX] ;stack routine offset
RET ;far return to start of called routine
ABSOLUTE ENDP
CODE ENDS
END

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

View File

@ -0,0 +1,18 @@
tron
defint a-z
for startrow = 1 to 12 step 12
for startcol = 16 to 64 step 24
call triangle (startrow,startcol)
next startcol
next startrow
sub triangle (vertical,horizontal) static
for row = 0 to 10
locate vertical+row,horizontal-row
for x = horizontal-row to horizontal+row
locate vertical+row,x
print "*"
next x
next row
end sub

Binary file not shown.

View File

@ -0,0 +1,7 @@
defint a-z
starta = 15 : startb=5 :startc=10 : startd = 40
call ex (startb,startc)
call tri (startd)
call square(starta)
end

View File

@ -0,0 +1,11 @@
defint a-z
startrow=1:startcol=16
for row = 0 to 10
locate startrow+row,startcol-row
for x = startcol-row to startcol+row
locate startrow+row,x
print "*"
next x
next row

View 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

Binary file not shown.

View File

@ -0,0 +1,11 @@
defint a-z
sub ex (startb,startc) static
size = 5
for x=0 to size
locate startb+x, startc+x
print "*"
locate startb+x, startc+size-x
print "*"
next x
end sub

Binary file not shown.

Binary file not shown.

View File

@ -0,0 +1,510 @@
TITLE INT86 - BASCOM software interrupt calling routine
;-----------------------------------------------------------------------
; R E V I S I O N H I S T O R Y
; 11-Mar-87 [1] RDK Since VARPTR returns negative values for DGROUP
; offsets 32K to 64K, add 64K to these values.
;-----------------------------------------------------------------------
;
; Microsoft Math Version
;
;
; Frame structure definition
; The following is used in INT86, INT86X, and PTR86.
ARG1 = 0AH ;pointer to first of three arguments
ARG2 = 08H ;pointer to second of three arguments
ARG3 = 06H ;pointer to third of three arguments
UCODE_SEG = 04H ;user code return pointer - segment
UCODE_OFF = 02H ;user code return pointer - offset
UCODE_BP = 00H ;user code BP register value (FRAME base)
; The following frame temp variables are used in INT86 and INT86X.
UCODE_FLGS = -02H ;user code flag register value
OUTARY_SEG = -04H ;output array pointer - segment
OUTARY_OFF = -06H ;output array pointer - offset
REG_NUM = -08H ;number of regs used (INT86=8, INT86X=10)
INT_ES = -0AH ;INT ES register value
INT_DS = -0CH ;INT DS register value
INT_FLGS = -0EH ;INT flags register value
INT_DI = -10H ;INT DI register value
INT_SI = -12H ;INT SI register value
INT_BP = -14H ;INT BP register value
INT_DX = -16H ;INT DX register value
INT_CX = -18H ;INT CX register value
INT_BX = -1AH ;INT BX register value
INT_AX = -1CH ;INT AX register value
FRM_SIZ = -1CH ;negative size of frame temporaries
; Locations past frame allocation used to recover post-INT BP value.
FRM_BP = -1EH ;frame BP saved for post-INT recovery
INT_BP_TMP = -20H ;temp location for INT BP register value
;***
; INT86, INT86X - 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 an integer array. The post-
; interrupt values of the registers are then stored in
; another integer array.
;
; CALL INT86[X] (int_no%,VARPTR(in_ary%(x)),VARPTR(out_ary%(y)))
;
; Inputs:
; int_no% = interrupt number (range 0 to 255) to execute
; in_ary%(x) to in_ary%(x+7) = input array. (INT86)
; in_ary%(x) to in_ary%(x+9) = input array. (INT86X)
; This array specifies the register values at the INT as
; follows (INT86 uses DGROUP to set DS and ES, not array
; elements 8 and 9.):
; in_ary%(x) = AX
; in_ary%(x+1) = BX
; in_ary%(x+2) = CX
; in_ary%(x+3) = DX
; in_ary%(x+4) = BP
; in_ary%(x+5) = SI
; in_ary%(x+6) = DI
; in_ary%(x+7) = flags
; in_ary%(x+8) = DS (if -1, then use DGROUP value) (INT86X only)
; in_ary%(x+9) = ES (if -1, then use DGROUP value) (INT86X only)
; Outputs:
; If no error:
; int_no% = unchanged (range 0 to 255)
; out_ary%(y) to out_ary%(y+9) = output array.
; This array will be set to the post-interrupt
; register values. It has the same structure
; as in_ary%.
; If error:
; int_no% = -1
; out_ary% unchanged. INT call is not performed.
; error occurs:
; first argument not 0 to 255 (2^8-1)
;[1] second or third arguments not in VARPTR range
;[1] -32767 (-2^15+1) to 1048575 (2^20-1)
; 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.
;***
DATA SEGMENT WORD PUBLIC 'DATA'
DATA ENDS
DGROUP GROUP DATA
CODE SEGMENT BYTE PUBLIC 'CODE'
ASSUME CS:CODE,DS:DGROUP,ES:DGROUP,SS:DGROUP
PUBLIC INT86
INT86 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 INT86_COMMON ;jump to common code
PUBLIC INT86X
INT86X 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 in the stack frame.
INT86_COMMON:
PUSHF ;push the flags on the stack
POP [BP].UCODE_FLGS ;put value in the stack frame
; From the third CALL argument on the stack, get the pointer to the
; VARPTR value of the output array and compute a far pointer to
; it. Then save the far pointer segment and offset in the frame.
MOV SI,[BP].ARG3 ;get pointer to s.p. VARPTR value
CALL SP_TO_PTR ;convert to far pointer in DX:AX
JC INT_ERROR_JUMP ;if error, then jump
MOV [BP].OUTARY_SEG,DX ;save far pointer segment in frame
MOV [BP].OUTARY_OFF,AX ;save far pointer offset in frame
; From the second CALL argument on the stack, obtain the far
; pointer to the input array in the same manner as above.
MOV SI,[BP].ARG2 ;get pointer to s.p. VARPTR value
CALL SP_TO_PTR ;convert to far pointer in DX:AX
JNC NO_INT_ERROR ;if no error, then jump
INT_ERROR_JUMP:
JMP INT_ERROR ;long jump to error routine
NO_INT_ERROR:
; Move eight or ten words (depending if executing INT86 or INT86X)
; of the integer input array from the far pointer computed to the frame.
MOV DS,DX ;move array pointer segment
MOV SI,AX ;and array offset - far pointer in DS:SI
LEA DI,[BP].FRM_SIZ ;get frame offset - ES = SS = DGROUP
MOV CX,[BP].REG_NUM ;eight or ten words to move
CLD ;movement is to higher memory
REP MOVSW ;move the array into the stack frame
PUSH ES ;get compiler data segment value on stack
POP DS ;restore so DS = ES = SS = compiler data seg
; 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) <--- fourth word past stack frame
; RETF 06 (hex: CA 06 00) <--- third and second word
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
MOV SI,[BP].ARG1 ;ptr to first CALL arg - interrupt number
MOV AX,[SI] ;from pointer, get integer value of INT type
OR AH,AH ;test if in range, 00 to FFH is legal
JNZ INT_ERROR_JUMP ;if not, then error - jump
MOV AH,AL ;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 CODE: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 INT86; or executing INT86X with array values of -1.
CMP WORD PTR [BP].REG_NUM,08H ;test if executing INT86
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
; Restore DS to SS. Move frame register values to the output
; array whose far pointer is in the frame.
PUSH SS ;put compiler data segment on stack
POP DS ;and restore DS register to it
LEA SI,[BP].FRM_SIZ ;get start of register area in frame
MOV ES,[BP].OUTARY_SEG ;get output array segment
MOV DI,[BP].OUTARY_OFF ;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 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:
PUSH SS ;put compiler data segment value on stack
POP DS ;and restore DS to its original value
MOV SI,[BP].ARG1 ;ptr to first CALL arg - interrupt number
MOV [SI],0FFFFH ;set interrupt number to -1 for error
MOV SP,BP ;deallocate temporary frame variables
POP BP ;return compiler frame pointer
RET 06 ;remove three CALL arguments and far return
INT86X ENDP
INT86 ENDP
;***
; PTR86 - Compute segment/offset from variable VARPTR value.
; Purpose:
; From a s.p. VARPTR of a compiler data variable, compute an
; equivalent segment and offset integer values. These variables
; are used to set INT86X register input array values.
;
; CALL PTR86 (varseg%,varoff%,VARPTR(var))
;
; Inputs:
; var = data variable (any type)
; Outputs:
; if no error, varseg% = segment part of far pointer to var
; varoff% = offset part of far pointer to var
; if error, varseg% = -1
; Modifies:
; AX, DX, and SI.
; Exceptions:
; None.
;***
PUBLIC PTR86
PTR86 PROC FAR
PUSH BP ;save BASCOM frame pointer on stack
MOV BP,SP ;establish program frame reference
MOV SI,[BP].ARG3 ;ptr to third CALL arg - VARPTR of variable
CALL SP_TO_PTR ;compute segment:offset in DX:AX
MOV SI,[BP].ARG1 ;ptr to first CALL arg - segment result
JC PTR86_ERROR ;if error, then jump
MOV [SI],DX ;put segment value into argument
MOV SI,[BP].ARG2 ;ptr to second CALL arg - offset result
MOV [SI],AX ;put offset value into argument
POP BP ;restore old frame pointer
RET 06H ;far return to caller - remove three stack args
PTR86_ERROR:
MOV [SI],0FFFFH ;put -1 in first arg for error report
POP BP ;restore old frame pointer
RET 06H ;far return to caller - remove three stack args
PTR86 ENDP
;***
; SP_TO_PTR - converts s.p. VARPTR value to segment/offset values
; Purpose:
; From the s.p. value pointed by DS:SI, convert to an integer
;[1] value. Report an error if not in the range -2^15 to 2^20-1.
;[1] Negative values are adjusted by 2^16 (65535) since VARPTR
;[1] maps the values 32768...65535 to -32768...-1 for interpreter
;[1] compatibility. Convert 20-bit address to segment and offset
; integer values using the standard 8086/8088 address computation:
;
; (16-bit segment)*16 + (16-bit offset) = 20-bit address
;
; Inputs:
; SI = pointer to s.p. address value
;
; The value is represented in Microsoft binary format, consisting
; of four bytes starting at the pointer given. The first three
; bytes are the low, middle, and high bytes of the number's
; mantissa while the fourth is the exponent. Sign-magnitude
; representation is used with the sign being the MSB of the high
; mantissa byte. All values are stored normalized with the
; mantissa MSB hidden with the sign bit. The binary point of the
; mantissa is before its MSB. The exponent is biased by 80H.
; A zero exponent implies a zero value independent of the mantissa's
; contents.
; Outputs:
; If no error:
; CF = 0 (carry cleared)
; DX = pointer segment integer result
; AX = pointer offset integer result
; If error:
; CF = 1 (carry set)
; DX,AX = undefined
; Modifies:
; None.
; Exceptions:
; None.
;***
SP_TO_PTR PROC NEAR
; Load s.p. number into DX:AX.
MOV AX,[SI] ;AH=middle mantissa - AL=low mantissa
MOV DX,[SI+2] ;DH=exponent - DL=sign/high mantissa
; If exponent is zero, then number value is zero.
OR DH,DH ;test if exponent is zero
JZ SP_ZERO ;if so, then jump
; Put in hidden MSB of mantissa.
OR DL,80H ;set hidden high-order mantissa bit
; Move data so DX:AX has 24-bit mantissa right-justified in 32 bits;
; and CX has 8-bit exponent right-justified in 16 bits.
PUSH CX ;save register...
XOR CX,CX ;clear both CH and CL
XCHG CL,DH ;DX:AX=24-bit mantissa - CX=exponent
; Remove 80H bias from exponent. Also subtract 12 (0CH) to move
; the binary from left of the 24th bit to left of the 12th bit of
; DX:AX. The resulting value is the number of left shifts of DX:AX
; resulting in a binary value with 20 bits left of the binary point
; and 12 bits right of it.
SUB CX,8CH ;remove 80H bias and 0CH to move b.pt. 12 bits
JE SP_NO_SHIFT ;if no shifting needed, then jump
JB SP_RIGHT_SHIFT ;if negative, then right shifting needed
SP_LEFT_SHIFT_LOOP:
SHL AX,1 ;shift low-order word left once
RCL DX,1 ;shift carry into high-order word
LOOP SP_LEFT_SHIFT_LOOP ;shift until done
JMP SHORT SP_NO_SHIFT ;shifting left done - jump
; A negative shift count is the inverse of the number of right
; shifts needed.
SP_RIGHT_SHIFT:
NEG CX ;compute shift count of DX:AX to the right
SP_RIGHT_SHIFT_LOOP:
SHR DX,1 ;shift high-order word right once
RCR AX,1 ;shift carry into low-order word
LOOP SP_RIGHT_SHIFT_LOOP ;loop until done...
;[1] If input value was negative, test magnitude for legal range
;[1] of 1 to 32768 (1 to 8000H). First decrement the value, so the
;[1] range is now 0 to 7FFFH. Test for the range and, if legal,
;[1] invert the significant bits.
SP_NO_SHIFT:
TEST BYTE PTR [SI+2],80H ;[1]test if value was negative
JZ SP_NOT_NEG ;[1]if not, then jump
SUB AH,10H ;[1]decrement value in high nybble of AH
SBB DX,0 ;[1]propagate if borrow was needed
TEST DX,NOT 7FFH ;[1]test if in legal range
JNZ SP_ERROR ;[1]jump to return error
XOR AH,0F0H ;[1]invert high nybble of AH
XOR DX,0FFFH ;[1]invert rest of value in DX
; The lower 4 bits of the 20-bit integer value are in the upper
; nybble of AX. Rotate and mask to move to lower nybble which
; will be the offset returned.
SP_NOT_NEG: ;[1]
ROL AX,1 ;rotate leftmost nybble in AX to rightmost...
ROL AX,1 ;second bit...
ROL AX,1 ;third bit...
ROL AX,1 ;fourth bit - done
AND AX,000FH ;leave only rightmost nybble left
; The upper 16 bits of the 20-bit integer value are in DX.
; This value is the integer divided by 16 and is therefore the
; paragraph value of the pointer. Since VARPTR values are
; relative to the compiler data segment, add the data segment
; value to compute the pointer segment.
MOV CX,DS ;get compiler data segment value
ADD DX,CX ;add to get pointer (permit wraparound)
POP CX ;restore register
CLC ;clear carry for success
RET ;near return to caller
; If zero, report 0 as the offset and the compiler data segment.
SP_ZERO:
XOR AX,AX ;clear offset result
MOV DX,DS ;set segment result to compiler DS
CLC ;clear carry for success
RET ;near return to caller
; If error, then set carry to report it.
SP_ERROR: ;[1]
POP CX ;[1]
STC ;set carry for failure
RET ;near return to caller
SP_TO_PTR ENDP
CODE ENDS
END

Binary file not shown.

View File

@ -0,0 +1,462 @@
TITLE INT8687 - BASCOM software interrupt calling routine
;-----------------------------------------------------------------------
; R E V I S I O N H I S T O R Y
; 12-Mar-87 [2] RDK In SP_TO_PTR, value popped in wrong order.
; 11-Mar-87 [1] RDK Since VARPTR returns negative values for DGROUP
; offsets 32K to 64K, add 64K to these values.
; Also add DGROUP to compute far pointer.
;-----------------------------------------------------------------------
;
; IEEE Math Coprocessor version
;
;
; Frame structure definition
; The following is used in INT86, INT86X, and PTR86.
ARG1 = 0AH ;pointer to first of three arguments
ARG2 = 08H ;pointer to second of three arguments
ARG3 = 06H ;pointer to third of three arguments
UCODE_SEG = 04H ;user code return pointer - segment
UCODE_OFF = 02H ;user code return pointer - offset
UCODE_BP = 00H ;user code BP register value (FRAME base)
; The following frame temp variables are used in INT86 and INT86X.
UCODE_FLGS = -02H ;user code flag register value
OUTARY_SEG = -04H ;output array pointer - segment
OUTARY_OFF = -06H ;output array pointer - offset
REG_NUM = -08H ;number of regs used (INT86=8, INT86X=10)
INT_ES = -0AH ;INT ES register value
INT_DS = -0CH ;INT DS register value
INT_FLGS = -0EH ;INT flags register value
INT_DI = -10H ;INT DI register value
INT_SI = -12H ;INT SI register value
INT_BP = -14H ;INT BP register value
INT_DX = -16H ;INT DX register value
INT_CX = -18H ;INT CX register value
INT_BX = -1AH ;INT BX register value
INT_AX = -1CH ;INT AX register value
FRM_SIZ = -1CH ;negative size of frame temporaries
; Locations past frame allocation used to recover post-INT BP value.
FRM_BP = -1EH ;frame BP saved for post-INT recovery
INT_BP_TMP = -20H ;temp location for INT BP register value
;***
; INT86, INT86X - 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 an integer array. The post-
; interrupt values of the registers are then stored in
; another integer array.
;
; CALL INT86[X] (int_no%,VARPTR(in_ary%(x)),VARPTR(out_ary%(y)))
;
; Inputs:
; int_no% = interrupt number (range 0 to 255) to execute
; in_ary%(x) to in_ary%(x+7) = input array. (INT86)
; in_ary%(x) to in_ary%(x+9) = input array. (INT86X)
; This array specifies the register values at the INT as
; follows (INT86 uses DGROUP to set DS and ES, not array
; elements 8 and 9.):
; in_ary%(x) = AX
; in_ary%(x+1) = BX
; in_ary%(x+2) = CX
; in_ary%(x+3) = DX
; in_ary%(x+4) = BP
; in_ary%(x+5) = SI
; in_ary%(x+6) = DI
; in_ary%(x+7) = flags
; in_ary%(x+8) = DS (if -1, then use DGROUP value) (INT86X only)
; in_ary%(x+9) = ES (if -1, then use DGROUP value) (INT86X only)
; Outputs:
; If no error:
; int_no% = unchanged (range 0 to 255)
; out_ary%(y) to out_ary%(y+9) = output array.
; This array will be set to the post-interrupt
; register values. It has the same structure
; as in_ary%.
; If error:
; int_no% = -1
; out_ary% 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.
;***
DATA SEGMENT WORD PUBLIC 'DATA'
DATA ENDS
DGROUP GROUP DATA
CODE SEGMENT BYTE PUBLIC 'CODE'
ASSUME CS:CODE,DS:DGROUP,ES:DGROUP,SS:DGROUP
PUBLIC INT86
INT86 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 INT86_COMMON ;jump to common code
PUBLIC INT86X
INT86X 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 in the stack frame.
INT86_COMMON:
PUSHF ;push the flags on the stack
POP [BP].UCODE_FLGS ;put value in the stack frame
; From the third CALL argument on the stack, get the pointer to the
; VARPTR value of the output array and compute a far pointer to
; it. Then save the far pointer segment and offset in the frame.
MOV SI,[BP].ARG3 ;get pointer to s.p. VARPTR value
CALL SP_TO_PTR ;convert to far pointer in DX:AX
JC INT_ERROR_JUMP ;if error, then jump
MOV [BP].OUTARY_SEG,DX ;save far pointer segment in frame
MOV [BP].OUTARY_OFF,AX ;save far pointer offset in frame
; From the second CALL argument on the stack, obtain the far
; pointer to the input array in the same manner as above.
MOV SI,[BP].ARG2 ;get pointer to s.p. VARPTR value
CALL SP_TO_PTR ;convert to far pointer in DX:AX
JNC NO_INT_ERROR ;if no error, then jump
INT_ERROR_JUMP:
JMP INT_ERROR ;long jump to error routine
NO_INT_ERROR:
; Move eight or ten words (depending if executing INT86 or INT86X)
; of the integer input array from the far pointer computed to the frame.
MOV DS,DX ;move array pointer segment
MOV SI,AX ;and array offset - far pointer in DS:SI
LEA DI,[BP].FRM_SIZ ;get frame offset - ES = SS = DGROUP
MOV CX,[BP].REG_NUM ;eight or ten words to move
CLD ;movement is to higher memory
REP MOVSW ;move the array into the stack frame
PUSH ES ;get compiler data segment value on stack
POP DS ;restore so DS = ES = SS = compiler data seg
; 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) <--- fourth word past stack frame
; RETF 06 (hex: CA 06 00) <--- third and second word
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
MOV SI,[BP].ARG1 ;ptr to first CALL arg - interrupt number
MOV AX,[SI] ;from pointer, get integer value of INT type
OR AH,AH ;test if in range, 00 to FFH is legal
JNZ INT_ERROR_JUMP ;if not, then error - jump
MOV AH,AL ;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 CODE: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 INT86; or executing INT86X with array values of -1.
CMP WORD PTR [BP].REG_NUM,08H ;test if executing INT86
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
; Restore DS to SS. Move frame register values to the output
; array whose far pointer is in the frame.
PUSH SS ;put compiler data segment on stack
POP DS ;and restore DS register to it
LEA SI,[BP].FRM_SIZ ;get start of register area in frame
MOV ES,[BP].OUTARY_SEG ;get output array segment
MOV DI,[BP].OUTARY_OFF ;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 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:
PUSH SS ;put compiler data segment value on stack
POP DS ;and restore DS to its original value
MOV SI,[BP].ARG1 ;ptr to first CALL arg - interrupt number
MOV [SI],0FFFFH ;set interrupt number to -1 for error
MOV SP,BP ;deallocate temporary frame variables
POP BP ;return compiler frame pointer
RET 06 ;remove three CALL arguments and far return
INT86X ENDP
INT86 ENDP
;***
; PTR86 - Compute segment/offset from variable VARPTR value.
; Purpose:
; From a s.p. VARPTR of a compiler data variable, compute an
; equivalent segment and offset integer values. These variables
; are used to set INT86X register input array values.
;
; CALL PTR86 (varseg%,varoff%,VARPTR(var))
;
; Inputs:
; var = data variable (any type)
; Outputs:
; if no error, varseg% = segment part of far pointer to var
; varoff% = offset part of far pointer to var
; if error, varseg% = -1
; Modifies:
; AX, DX, and SI.
; Exceptions:
; None.
;***
PUBLIC PTR86
PTR86 PROC FAR
PUSH BP ;save BASCOM frame pointer on stack
MOV BP,SP ;establish program frame reference
MOV SI,[BP].ARG3 ;ptr to third CALL arg - VARPTR of variable
CALL SP_TO_PTR ;compute segment:offset in DX:AX
MOV SI,[BP].ARG1 ;ptr to first CALL arg - segment result
JC PTR86_ERROR ;if error, then jump
MOV [SI],DX ;put segment value into argument
MOV SI,[BP].ARG2 ;ptr to second CALL arg - offset result
MOV [SI],AX ;put offset value into argument
POP BP ;restore old frame pointer
RET 06H ;far return to caller - remove three stack args
PTR86_ERROR:
MOV [SI],0FFFFH ;put -1 in first arg for error report
POP BP ;restore old frame pointer
RET 06H ;far return to caller - remove three stack args
PTR86 ENDP
;***
; SP_TO_PTR - converts s.p. VARPTR value to segment/offset values
; Purpose:
; From the s.p. value pointed by DS:SI, convert to an integer
; value. Report an error if not in the range 0 to 2^20-1.
; Convert 20-bit address to segment and offset integer values
; using the standard 8086/8088 address computation:
;
; (16-bit segment)*16 + (16-bit offset) = 20-bit address
;
; Inputs:
; SI = pointer to s.p. address value
;
; If IEEE, the value is represented in IEEE floating point binary format,
; consisting of four bytes starting at the pointer given.
;
; If MS-Math, the value is represented in Microsoft binary format,
; consisting of four bytes starting at the pointer given. The first three
; bytes are the low, middle, and high bytes of the number's mantissa
; while the fourth is the exponent. Sign-magnitude representation is used
; with the sign being the MSB of the high mantissa byte. All values are
; stored normalized with the mantissa MSB hidden with the sign bit. The
; binary point of the mantissa is before its MSB. The exponent is biased
; by 80H. A zero exponent implies a zero value independent of the
; mantissa's contents.
;
; Outputs:
; If no error:
; CF = 0 (carry cleared)
; DX = pointer segment integer result
; AX = pointer offset integer result
; If error:
; CF = 1 (carry set)
; Modifies:
; None.
; Exceptions:
; None.
;***
SP_TO_PTR PROC NEAR
;
; Use coprocessor to perform float to int conversion
;
FLD DWORD PTR [SI] ;Coprocessor ST(0) = s.p. number
PUSH BX ;Preserve
PUSH AX ;Create 4 byte temp on stack
PUSH AX
MOV BX,SP ;[BX] = pointer to 4 byte temp
FISTP DWORD PTR [BX] ;[BX] = pointer to converted int
FWAIT
POP AX ;[2]
POP DX ;[2][DX:AX] = 20 bit physical address
POP BX ;Restore
;
; Check for an invalid value
;
TEST DX,0FFF0H
JZ SP_CONVERT ;[1]if between 0 and 2^20, then jump
CMP DX,0FFFFH ;[1]negative - test high-order word
JNZ SP_ERROR ;[1]if not all ones (less than -64K), then err
TEST AH,80H ;[1]test if less than -32K
JZ SP_ERROR ;[1]if so, then also an error
NOT DX ;[1]invert high-order word to zero
;[1] Value now in DX:AX - 0 to 2^20-1 - 000x:xxxx.
;[1] Normalize pointer to xxxx:000x and add DGROUP value.
SP_CONVERT:
PUSH CX ;[1]save register...
MOV CX,12D ;[1]will double-shift 12 times...
SP_LOOP: ;[1]
SHL AX,1 ;[1]shift the low-order word...
RCL DX,1 ;[1]...and the high-order word with carry
LOOP SP_LOOP ;[1]loop until done
MOV CL,4 ;[1]value now xxxx:x000 - need xxxx:000x, so...
ROL AX,CL ;[1]rotate low-order word - now xxxx:000x
MOV CX,DS ;[1]get the DGROUP value
ADD DX,CX ;[1]and add it to get far pointer in DX:AX
POP CX ;[1]restore register
CLC ;clear carry for success
RET ;near return to caller
; If error, then set carry to report it.
SP_ERROR:
STC ;set carry for failure
RET ;near return to caller
SP_TO_PTR ENDP
CODE ENDS
END

Binary file not shown.

Binary file not shown.

Binary file not shown.

View File

@ -0,0 +1,751 @@
REM $Title:'Microsoft PPRINT- Formatted Print Utility'
REM $Subtitle:'Introduction'
'
' Microsoft PPRINT- Formatted Print Utility
' Copyright (C) Microsoft Corporation - 1986
'
' This program is designed to format QuickBASIC source files that include
' the formatting metacommands found in QuickBASIC V1.00 and earlier
' Microsoft BASIC Compilers.
'
' The Metacommands processed by PPRINT are:
'
' TITLE: 'title' Prints 'title' at the top of each page
' SUBTITLE: 'subtitle' Prints 'subtitle' below the title area
' LINESIZE:n Sets output line width to n
' PAGESIZE:n Sets the output page size to n
' PAGE Skips to next page
' PAGEIF:n Skips to next page if there are fewer than n
' lines left on current page
' SKIP[:n] Skips n lines or to top of next page
' LIST- Turns OFF output of lines
' LIST+ Turns ON output of lines
'
'
' USAGE: The PPRINT Utility has the following usage:
'
' PPRINT InputFile, [OutputFile]
'
' If the OutputFile is ommitted, LPT1: is the default
'
' COMPILATION:
'
' Since the PPRINT utility is distributed in source form (PPRINT.BAS)
' You must compile it before using. Suggested compilation procedures are
' as follows:
'
' 1) Load PPRINT.BAS into the QuickBASIC editor
' 2) Select "Compile..." from the RUN Menu
' 3) Select ".EXE" from the output options section
' 4) press the "Compile" button or press return
'
' These 4 steps should create a file PPRINT.EXE on your default
' drive.
'
' REVISION HISTORY:
'
' 12/1/86- GEL - Fixed TARs # 57720 & 56937
'
rem $subtitle:'Global Declarations'
rem $page
DEFINT a - z
DIM KeyWordCount, LineCount, Seps$
DIM KeyBoard, Console
DIM InputFile$, OutputFile$
DIM Temp$,x ' temp variables
'
' global variables for handling metacommands
DIM Out.Title$, Out.Subtitle$, MetaCommand.On
DIM Out.LineSize, Out.Pagesize, Out.List, Out.LineCount, Out.BlankBottom
DIM Out.PageNum
REM $subtitle:'FnToUpper- Converts To Uppercase'
rem $page
'
' FNToUpper$ - Convert string to uppercase
' Description:
' This routine converts a string to uppercase. If already uppercase
' nothing is done. Returns a null string if input is null
' Input:
' InString$ - string to convert
' Output:
' FNToUpper$ - uppercase string
Def FNToUpper$(InString$)
static LenInString, AscChar, Index, IndexInString
LenInString = len(InString$)
' Exit if input string is empty (null)
if (LenInString = 0) then
FNToUpper$ = ""
Exit Def
end if
for IndexInstring = 1 to LenInString
AscChar = asc(mid$(InString$, IndexInstring, 1))
' &hdf is special bit pattern that converts from lower to upper
if ((AscChar >= asc("a")) and (AscChar <= asc("z"))) then
AscChar = AscChar and &hdf
mid$(InString$, IndexInstring, 1) = chr$(AscChar)
end if
next IndexInString
FNToUpper$ = InString$
End Def
rem $subtitle:'FnTabsToBlanks- Converts TABs to Blanks'
rem $page
'
' FnTabsToBlanks- turns TABs into blanks in the given string
'
' Input: Source$
' Output Source$ with ALL TABs as 3 Blanks
' Note: If TABs are set at a value different from 3, change the following
' procedure in the 'Then' part of the IF statement
'
DEF FNTabsToBlanks$(source$)
STATIC Temp$,i
Temp$ = ""
If Instr(Source$, Chr$(9)) = 0 Then FnTabsToBlanks$ = Source$: Exit Def
For i = 1 to Len(source$)
If ASC(Mid$(Source$,i,1)) = 9 Then
Temp$ = Temp$ + Space$(3) ' replace with 3 spaces
Else
Temp$ = Temp$ + Mid$(source$,i,1)
End If
Next i
FnTabsToBlanks$ = Temp$
End Def
rem $subtitle:'FnStrSpn- String Spanner'
rem $page
'
' FNStrSpn - Get the index of the first character within InString$ that is
' NOT one of the characters from Separater$
' Description:
' This routine will search the parameter string InString$ until it finds
' a character that is not part of the Separater string. This can be used
' with FNStrBrk to isolate strings within strings that are separated by
' blanks, comma etc. whatever is specified in Separater$. This is especially
' helpful in extracting parameters from the command line. See FNGetToken$
' for example of use.
'
' Input:
' InString$ = string to search
' Separater$ = string of Separater
'
' Output:
' FNStrSpn = index into InString$ if 0 then all character in Separater$
' are in InString$
Def FNStrSpn(InString$, Separater$)
static LenInString, LenSeparater, StartFound, IndexSeparater, IndexInString
static ChTemp$
LenInString = Len(InString$)
LenSeparater = Len(Separater$)
' Examine each character from InString$ to see if it is in Separater$
for IndexInString = 1 to LenInString
ChTemp$ = Mid$(InString$, IndexInString, 1)
StartFound = false
' search all of the Separaters to see of any equal this character
for IndexSeparater = 1 to LenSeparater
if (ChTemp$ = Mid$(Separater$, IndexSeparater, 1)) then
goto NextChar
end if
next IndexSeparater
' found a character not equal to one of the Separaters$
' exit from loops
StartFound = true
goto EndStrSpn
NextChar:
Next IndexInString
EndStrSpn:
if (StartFound) then
FNStrSpn = IndexInString
else
FNStrSpn = 0
end if
End Def
rem $subtitle:'FnStrBrk- String Breaker'
rem $page
'
' FNStrBrk - finds the first occurance of any character in string2$ in
' string1$
' Description:
' This routine is the opposite to FNStrSpn. It finds the first occurance
' of one of the characters from String2$ within String$. It is used
' generally for search from specific strings within strings. See FNSeparater
' on use. See FNGetToken$ to see the routines in use.
'
' Input:
' string1$ = string to search for first occurance
' string2$ = string of characters to search for
' Output:
' FNStrBrk = index to character in string1$ of first occurance
'
' Uses:
' LenString1 = length parameter string
' ChTemp$ = temp used for current character from String1$
' IndexString1 = current indices into parameter string
'
Def FNStrBrk(String1$, String2$)
static LenString1, IndexString1, StartFound
static ChTemp$
LenString1 = Len(String1$)
' Search String1$ until one of the characters from String2$ is found
' or run out of characters from String$2
for IndexString1 = 1 to LenString1
ChTemp$ = Mid$(String1$, IndexString1, 1)
if (instr(String2$, ChTemp$)) then
StartFound = true
FNStrBrk = IndexString1
Exit Def
end if
Next IndexString1
FnStrBrk = 0
End Def
rem $subtitle:'FnGetToken- Gets a Token'
rem $page
'
' FNGetToken$ - Extract a token for a string.
' Description:
' This routine extracts tokens from strings. A token is a word that is
' surrounded by separaters, such as spaces or commas. It is usually the
' word of interest and examining sentences or commands. If the string
' to search for tokens "Search$" is null (.i.e "") then the last
' non-null string passed will be used. The allows for multiple calls
' to FNGetToken$ to move through the string. EG: The sequences of calls
' would be:
' token$ = FNGetToken$("token string, a short one", " ,")
' while (token$ <> "")
' print token$
' token$ = FNGetToken$("", " ,")
' wend
' This will return "token", "string", "a", "short", "one"
'
' Note that the token is returned as an Uppercase character string.
'
' Input:
' Search$ = string to search
' InSeps$ = String of Seps$
' Output:
' FNGetToken$ = next token
' Uses:
' TokenString$ = last non-null string passed as parameter (do not modify)
' TokenIndex2 = index to last separater (do not modify)
'
def FNGetToken$(Search$, InSeps$)
static TokenIndex1
' Null strings indicate use of last string used
' TokenString$ is set to last string if Search$ is not null
if (Search$ = "") then
Search$ = TokenString$
else
TokenIndex2 = 1
TokenString$ = Search$
end if
' If last separater position is past end of search string then no more
' tokens can be in string, since searching is started from this position
' Exit with null return in this case
if (TokenIndex2 >= len(Search$)) then
FNGetToken$ = ""
Exit Def
end if
' Section out a token from the search string. This is done by finding the
' start of a token then locating it's end by the start of separaters
TokenIndex1 = FNStrSpn(mid$(Search$, TokenIndex2, len(Search$)), InSeps$)
' If no more token bump to end of line so we move past current point
if (TokenIndex1 = 0) then
TokenIndex1 = len(Search$)
else
TokenIndex1 = TokenIndex1 + TokenIndex2 - 1
end if
TokenIndex2 = FNStrBrk(mid$(Search$, TokenIndex1, len(Search$)), InSeps$)
' If separater position (end of token) came back zero the token must be
' up against end of string. Set the separater position one past string
' length so that size of token computation is correct and next call
' with same string will return null for no more tokens
if (TokenIndex2 = 0) then
TokenIndex2 = len(Search$) + 1
else
TokenIndex2 = TokenIndex1 + TokenIndex2 - 1
end if
' Cut out token from search string and convert to uppercase.
' It is converted to uppercase since string compares are case sensitive
FNGetToken$ = mid$(Search$,TokenIndex1,TokenIndex2 - TokenIndex1)
end def
rem $subtitle:'FnIsNumber- Is a Number?'
rem $page
'
' FNIsNumber - Checks to see if character a number or alpha
' Description:
' This routine returns true if character passed is in the range 0 - 9
' It returns false if not. It is used to tell wither a token is
' a number or alpha.
' Input:
' Char - character to check
' Output:
' FNIsNumber - true if within 0 - 9
'
def FNIsNumber(Char$)
static CharAsc
if (Char$ = "") then
FNIsNumber = false
else
CharAsc = asc(Char$)
FNIsNumber = ((CharAsc >= asc("0")) and (CharAsc <= asc("9")))
end if
end def
rem $subtitle:'FnIsChar- Is a character?'
rem $page
def FNIsChar(Char$)
static CharAsc
CharAsc = asc(Char$)
FNIsChar = ((CharAsc >= asc("A")) and (CharAsc <= asc("z")))
end def
rem $subtitle:'FnIsKeyword- Is a Keyword?'
rem $page
' FNIsKeyWord - returns true if specified string is a BASIC key word
' Description:
' Checks keyword list agains String$, non-zero return if keyword
'
def FNIsKeyWord(Key$)
static KeyWord$, AscCh, t
if (len(Key$) > 0) then
t = asc(key$)
while t < 33 AND Key$ <> "" ' strip off all spaces and below
key$= mid$(key$,2)
If key$ <> "" then t = asc(key$) Else FNIsKeyword=0: Exit Def
wend
Key$ = FNToUpper$(Key$)
AscCh = (asc(Key$) - asc("A") + 1)
if ((AscCh >= 0 ) and (AscCh <= 24)) then
on (AscCh) gosub AKey, BKey, CKey, DKey, EKey, FKey, GKey, HKey, _
IKey, JKey, KKey, LKey, MKey, NKey, OKey, PKey, _
QKey, RKey, SKey, TKey, UKey, VKey, WKey, XKey, _
YKey, ZKey
read KeyWord$
while (KeyWord$ <> "")
if (KeyWord$ = Key$) then
FNIsKeyWord = TRUE
exit def
end if
read KeyWord$
wend
end if
end if
FNIsKeyWord = FALSE
exit def
AKey:
DATA ABS, AND, APPEND, AS, ASC, ATN, AUTO, ""
restore AKey: return
BKey:
DATA BEEP, BLOAD, BSAVE, ""
restore BKey: return
CKey:
DATA CALL, CALLS, CDBL, CHAIN, CHDIR, CHR$, CINT, CIRCLE, CLEAR
DATA CLOSE, CLS, COLOR, COM, COMMAND$, COMMON, CONT, COS, CSNG
DATA CSRLIN, CVD, CVI, CVS, "", ""
restore CKey: return
DKey:
DATA DATA, DATE$, DEF, DEFDBL, DEFINT, DEFSNG, DEFSTR, DEF FN, DEF USR, DELETE
DATA DIM, DRAW, ""
restore DKey: return
EKey:
DATA EDIT, ELSE, END, ENVIRON, ENVIRON$, EOF, EQV, ERASE
DATA ERL, ERR, ERROR, EXIT, EXP, ""
restore EKey: return
FKey:
DATA FIELD, FILES, FIX, FOR, FRE, ""
restore FKey: return
GKey:
DATA GET, GO, GOSUB, GOTO, ""
restore GKey: return
HKey:
DATA HEX$, ""
restore HKey: return
IKey:
DATA IF, IMP, INKEY$, INP, INPUT, INPUT$, INPUT$, INSTR, INT, ""
restore IKey: return
JKey:
DATA ""
restore JKey: return
KKey:
DATA KEY, KILL, ""
restore KKey: return
LKey:
DATA LCOPY, LEFT$, LEN, LET, LINE, LIST, LBOUND, LLIST, LOAD
DATA LOC, LOCAL, LOCATE, LOCK, LOF, LOG, LPOS, LPRINT, LSET, ""
restore LKey: return
MKey:
DATA MERGE, MID$, MKD$, MKI$, MKS$, MKDIR, MOD, MOTOR, ""
restore MKey: return
NKey:
DATA NAME, NEW, NEXT, NOT NULL, ""
restore NKey: return
OKey:
DATA OCT$, ON, OPEN, OPTION, OR, OUT, OUTPUT, ""
restore OKey: return
PKey:
DATA PAINT, PALETTE, PEEK, PEN, PLAY, PMAP
DATA POINT, POKE, POS, PRESET, PRINT, PSET, PUT, ""
restore PKey: return
QKey:
DATA ""
restore QKey: return
RKey:
DATA RANDOMIZE, READ, REDIM, REM, RENUM, REM, RENUM
DATA RESTORE, RESUME, RETURN, RIGHT$, RMDIR, RND, RSET, RUN, ""
restore RKey: return
SKey:
DATA SAVE, SCREEN, SEG, SGN, SHARED, SHELL, SIN, SOUND, SPACE
DATA SPC, SQR, STATIC, STEP, STICK, STOP, STR, STRIG, STRING
DATA SUB, SWAP, SYSTEM, ""
restore SKey: return
TKey:
DATA TAB, TAN, THEN, TIME, TIMER, TO, TROFF, TRON, ""
restore TKey: return
UKey:
DATA UBOUND, UNLOCK, USING, ""
restore UKey: return
VKey:
DATA VAL, VARPTR, VIEW, ""
restore VKey: return
WKey:
DATA WAIT, WEND, WHILE, WIDTH, WINDOW, WRITE, ""
restore WKey: return
XKey:
DATA XOR, ""
restore XKey: return
YKey:
DATA ""
restore YKey: return
ZKey:
DATA ""
restore ZKey: return
end def
rem $subtitle:'FnIsMetacommand- Is a Metacommand?'
rem $page
'FNIsMetaCommand- returns non-zero if source$ is a meta command of
' the form "'$metacommand" or "$metacommand"
'
' Input:
' Source$ - source string to determine if metacommand
'
def FnIsMetacommand(source$)
' The following is a list of the metacommands processed by this program
Meta$ = "TITLE SUBTITLE LINESIZE PAGESIZE PAGE PAGEIF SKIP LIST- LIST+ LIST"
if (mid$(source$,1,1)) = "'" then source$=mid$(source$,2)
if ((mid$(source$,1,1)) <> "$") OR (len(source$) < 4 ) then
FnIsMetacommand = 0
exit def
else
source$=Mid$(source$,2) ' get rid of the $
source$ = FnToUpper$(source$) 'convert to uppercase
x = instr(meta$,source$)
if x <> 0 then FnIsMetacommand = -1 else FnIsMetacommand = 0
end if
end def
rem $subtitle:'InQuote'
rem $page
' InQuote- determines whether or not we are in the middle of a
' quoted literal
'
' Input: Target$- string to see if it contains a double quote character
' Output: either 1 or 0, toggles state of Quoted.Literal
'
SUB InQuote(Target$, Quoted.Literal) STATIC
STATIC x,xi
x= INSTR(1,target$,chr$(34)) ' is there a quote in the string??
IF x = 0 then
Exit SUB ' no quote chracters, exit...
ELSE
x1 = Instr(x+1, target$,chr$(34)) ' look for a 2nd quote
if x1 = 0 then quoted.Literal = NOT Quoted.Literal
END IF
END SUB
rem $subtitle:'Write.Outputfile- writes 1 line'
rem $page
' Write.Outputfile- Writes one line to the output file, handling all the
' all the parameters set up by metacommands.
' Assumptions:- This routine assumes that channel #2 has been opened for output
'
' Input:
' OutputLine$ - The line to output
' Output:
' None
' Uses:
' Out.Title$, Out.SubTitle$, Out.LineSize, Out.PageSize, Out.List,
' Out.LineCount, Out.BlankBottom, MetaCommand.On, True, False
SUB Write.Outputfile(outputLine$) STATIC
SHARED Out.Title$, Out.SubTitle$, Out.LineSize, Out.PageSize, Out.List
SHARED Out.LineCount, Out.BlankBottom, MetaCommand.On, True, False
If Out.List = False THEN Exit Sub 'Listing is OFF
If MetaCommand.On Then MetaCommand.On = False: Exit Sub ' Don't Print the metacommand line
IF Out.LineCount = 0 Then CALL Out.Header 'must be first time into this routine
' Convert all TABs in the line to Blanks
OutputLine$ = FnTabsToBlanks$(outputline$)
'Output the line, given the page width
OutLine.Length = Len(outputLine$)
While OutLine.Length > Out.LineSize-1
IF (Out.LineCount > (Out.PageSize-Out.BlankBottom)) AND (Out.PageSize <> 255) THEN CALL Out.Header
PRINT #2, Mid$(OutputLine$,1,Out.LineSize-1)
OutputLine$ = Mid$(OutputLine$,Out.LineSize) 'start at next char
OutLine.Length = Len(outputLine$)
Out.LineCount = Out.LineCount + 1
Wend
IF (Out.LineCount > (Out.PageSize-Out.BlankBottom)) AND (Out.PageSize <> 255) THEN CALL Out.Header
PRINT #2, Mid$(OutputLine$,1,Out.LineSize-1)
Out.LineCount = Out.LineCount + 1
End Sub
rem $subtitle:'Out.Header- Writes the Header Info'
rem $page
' Out.Header - Output the header to the output file
'
' Assumptions- Assumes Channel #2 is open for output
' Input:
' None
' Output:
' None
' Uses:
' Out.Title$, Out.SubTitle$, Out.LineSize, Out.PageSize, Out.List,
' Out.LineCount
SUB Out.Header STATIC
SHARED Out.Title$, Out.SubTitle$, Out.LineSize
SHARED Out.LineCount, Out.PageNum, Out.List
If Out.List = 0 Then exit sub
' first update the screen
Locate 2,5:print "Microsoft PPRINT: Formatted Print Utility"
locate 4,5:print space$(60)
locate 4,5:print "Currently printing Page: ";Out.Pagenum
if out.pagenum > 1 then Print #2, Chr$(12) ' The FF character
Print #2, Mid$(Out.Title$,1,Out.LineSize);
page$ = "Page"+string$(4-len(str$(out.pagenum))," ")+str$(out.PageNum)
print #2,Tab(Out.LineSize-len(page$));Page$
print #2, Mid$(Out.Subtitle$,1,Out.LineSize);
print.date$ = left$(date$,6)+right$(date$,2)
print #2, Tab(Out.LineSize-8);print.date$
print #2, Tab(Out.LineSize-8);Time$
Print #2,Tab(Out.LineSize-35);"Microsoft QuickBASIC Compiler V2.01"
Print #2, "" ' add a blank line
Out.LineCount = 7
Out.PageNum = Out.PageNum + 1
END SUB
rem $subtitle:'ProcessMetacommand- Process 1 Metacommand'
rem $page
' ProcessMetaCommand- Determines which meta command it is and takes
' the appropriate action(s)
'
' Input
' Token$- Last token found
' Output
' None, except the action associated with the metacommand
'
SUB ProcessMetaCommand( Token$) STATIC
SHARED Out.Title$, Out.SubTitle$, Out.LineSize, Out.PageSize, Out.List
SHARED Out.LineCount, Out.BlankBottom, MetaCommand.On, True, False
SHARED OutputFile$
STATIC X, Meta1$
' Each item in the following list is an a 10 character boundary so that
' I can find the index, divide by 10, and use the ON...GOTO contruct
meta1$ = " TITLE SUBTITLE LINESIZE PAGE PAGESIZE PAGEIF SKIP LIST- LIST+"
if (mid$(token$,1,1)) = "'" then token$=mid$(token$,2)
token$=Mid$(token$,2) ' get rid of the $
token$ = FnToUpper$(token$) 'convert to uppercase
MetaCommand.On = -1
x = instr(Meta1$,token$)/10
ON x GOTO Title, Subtitle, LineSize, Page, PageSize, Pageif, Skip, ListOff, ListOn
Title:
arg$=FnGetToken$("","'"): Arg$=FnGetToken$("","'")
Out.Title$ = Arg$
Exit Sub
Subtitle:
arg$=FnGetToken$("","'"): Arg$=FnGetToken$("","'")
Out.SubTitle$ = Arg$
Exit Sub
LineSize:
arg$=FnGetToken$("","': ")
Out.LineSize=Val(arg$)
IF OutputFile$ = "LPT1:" THEN WIDTH #2,Out.LineSize 'FIX #57720
Exit Sub
Page:
CALL Out.Header
Exit Sub
PageSize:
arg$=FnGetToken$("","': ")
Out.PageSize=Val(arg$)
Out.LineCount = Out.LineCount MOD Out.PageSize
Exit Sub
Pageif:
arg$=FnGetToken$("","': ")
x =Val(arg$)
If (Out.PageSize-Out.BlankBottom-x) <= Out.LineCount Then CALL Out.Header
Exit Sub
Skip:
arg$=FnGetToken$("","': ")
x =Val(arg$)
IF (Out.LineCount+x) > (Out.PageSize-Out.BlankBottom) Then
Call Out.Header
Else
For i=1 to x
Call Write.OutputFile(" ")
Next i
END IF
MetaCommand.On = -1 ' Fix #56937
Exit Sub
ListOff:
Out.List = False
Exit Sub
ListOn:
Out.List= True
Exit Sub
END SUB
rem $subtitle:'GetFilenames- Gets the I/O filenames'
rem $page
'
' GetFileNames - Parses the input and output file names from command$
' Description:
' This routine retrieves the input and output file names. These should
' be separated by a comma with the input file name coming first.
' Input:
' Command$ - Command line
' true, false - logical flags
' Output:
' InputFile$, OutputFile$ - Input/Output file name
'
sub GetFileNames static
shared InputFile$, OutputFile$, Seps$, true, false
if (Command$ = "") then
print " Microsoft PPrint: Formatted Print Utility"
print " "
Input " Input Filename (return to terminate)";InputFile$
If inputfile$ = "" Then Exit Sub
Input " Output Filename (default is LPT1:)";OutputFile$
CLS
else
InputFile$ = FNGetToken$(Command$, Seps$)
OutputFile$ = FNGetToken$("", " ") 'next token is outputfilename
end if
ExitGet:
'Add .bas if filename has no extension
if Instr(InputFile$,".") = 0 then InputFile$ = InputFile$ + ".bas"
if (OutputFile$ = "") then OutputFile$ = "LPT1:"
end sub
rem $subtitle:'InitSys- Initialize the System'
rem $page
'
' initialize the system
'
SUB initsys STATIC
SHARED true, false, KeyWordCount, Seps$
SHARED Out.Title$, Out.SubTitle$, Out.LineSize, Out.PageSize, Out.List, Out.LineCount, Out.BlankBottom, Out.PageNum
Seps$ = " ,: ": true = -1: false = 0
Out.Title$ = ""
Out.SubTitle$ = ""
Out.LineSize = 80
Out.PageSize = 66
Out.List = true
Out.LineCount = 0
Out.BlankBottom = 6 '6 lines are left blank at the bottom of each
' page unless pagesize=255 meaning an infinate
' page.
Out.PageNum = 1
MetaCommand.On = 0
END SUB
rem $subtitle:'MAIN PROGRAM'
rem $page
main:
Call InitSys
Call GetFileNames
If Inputfile$ = "" Then goto Exitmain
open InputFile$ for input as #1
open outputfile$ for output as #2
while not eof(1)
line input #1, LineCur$
outputLine$ = LineCur$
OutputIndex = 1
TokenCur$ = FNGetToken$(LineCur$, Seps$)
while (TokenCur$ <> "")
CALL InQuote(TokenCur$,Quoted.Literal)
IF FNIsKeyWord(TokenCur$) then
' Make uppercase
' stuff into line at appropriate position
'
Temp$=FNToUpper$(TokenCur$)
x = Instr(OutputIndex,OutputLine$,TokenCur$)
IF NOT Quoted.Literal THEN MID$(OutPutLine$,x) = Temp$ 'replace with uppercase
OutputIndex = x + len(temp$)
ELSEIF FnIsMetacommand(tokencur$) Then
OutputIndex = OutputIndex + Len(TokenCur$)
' process the metacommand
Call ProcessMetaCommand(TokenCur$)
ELSE
'move index across line
OutputIndex = OutputIndex + Len(TokenCur$)
END IF
TokenCur$ = FNGetToken$("", Seps$)
wend
Call Write.Outputfile(OutputLine$)
wend
Print #2,chr$(12) 'send one last FF character
CLOSE ' Close all files
Exitmain:
end

View File

@ -0,0 +1,50 @@
title prefix
_CODE segment para public 'BC_CODE'
_CODE ends
CSEG segment para public 'CODESG'
CSEG ends
CODE segment para public 'CODE'
CODE ends
SHELL segment para public 'CODESG'
SHELL ends
CLEAR segment para public 'CODESG'
CLEAR ends
BC_ICN_CODE segment para public 'INIT_CODE'
BC_ICN_CODE ends
BC_IDS_CODE segment para public 'INIT_CODE'
BC_IDS_CODE ends
INIT_CODE segment para public 'INIT_CODE'
INIT_CODE ends
; DSEG must come first and not be CONST or _DATA so that other language
; obj's do not mess with the location of DSEG
DSEG segment common 'DATASG'
DSEG ends
CONST segment para public 'CONST'
CONST ends
_BSS segment word public 'BSS'
_BSS ends
c_common segment word public 'BSS'
c_common ends
DATA segment para public 'DATA'
DATA ends
BC_DATA segment word public 'BC_VARS'
BC_DATA ends
named_common segment word common 'BC_VARS'
named_common ends
BC_FT segment word public 'BC_SEGS'
BC_FT ends
BC_CN segment para public 'BC_SEGS'
BC_CN ends
BC_DS segment para public 'BC_SEGS'
BC_DS ends
COMMON segment para common 'BLANK'
COMMON ends
LAST_SEGMENT segment para public 'LAST_SEGMENT'
LAST_SEGMENT ends
DGROUP group DSEG,CONST,_BSS,DATA,BC_DATA,BC_FT,BC_CN,BC_DS,COMMON
public __acrtused
__acrtused equ 1
end

Binary file not shown.

View File

@ -0,0 +1,82 @@
TITLE PREFIX87 - segment ordering module for assembly programs
_CODE segment para public 'BC_CODE'
_CODE ends
CSEG segment para public 'CODESG'
CSEG ends
CODE segment para public 'CODE'
CODE ends
SHELL segment para public 'CODESG'
SHELL ends
CLEAR segment para public 'CODESG'
CLEAR ends
BC_ICN_CODE segment para public 'INIT_CODE'
BC_ICN_CODE ends
BC_IDS_CODE segment para public 'INIT_CODE'
BC_IDS_CODE ends
INIT_CODE segment para public 'INIT_CODE'
INIT_CODE ends
; DSEG must come first and not be CONST or _DATA so that other language
; obj's do not mess with the location of DSEG
DSEG segment common 'DATASG'
DSEG ends
CONST segment para public 'CONST'
CONST ends
_BSS segment word public 'BSS'
_BSS ends
c_common segment word public 'BSS'
c_common ends
DATA segment para public 'DATA'
DATA ends
BC_DATA segment word public 'BC_VARS'
BC_DATA ends
named_common segment word common 'BC_VARS'
named_common ends
BC_FT segment word public 'BC_SEGS'
BC_FT ends
BC_CN segment para public 'BC_SEGS'
BC_CN ends
BC_DS segment para public 'BC_SEGS'
BC_DS ends
COMMON segment para common 'BLANK'
COMMON ends
LAST_SEGMENT segment para public 'LAST_SEGMENT'
LAST_SEGMENT ends
DGROUP group DSEG,CONST,_BSS,DATA,BC_DATA,BC_FT,BC_CN,BC_DS,COMMON
public __acrtused
__acrtused equ 1
fINT EQU 0CDH
fFWAIT EQU 09BH
fESCAPE EQU 0D8H
fNOP EQU 090H
fES EQU 026H
fCS EQU 02Eh
fSS EQU 036h
fDS EQU 03Eh
BEGINT equ 084h ; QB 3 beginning interrupt
PUBLIC FIWRQQ,FIERQQ,FIDRQQ
PUBLIC FISRQQ,FJSRQQ,FIARQQ,FJARQQ,FICRQQ,FJCRQQ ; new fixups
FIDRQQ EQU (fINT + 256*(BEGINT + 0)) - (fFWAIT + 256*fESCAPE)
FIERQQ EQU (fINT + 256*(BEGINT + 8)) - (fFWAIT + 256*fES)
FIWRQQ EQU (fINT + 256*(BEGINT + 9)) - (fNOP + 256*fFWAIT)
FIARQQ EQU (fINT + 256*(BEGINT + 8)) - (fFWAIT + 256*fDS)
FJARQQ EQU 256*(((0 shl 6) or (fESCAPE and 03Fh)) - fESCAPE)
FISRQQ EQU (fINT + 256*(BEGINT + 8)) - (fFWAIT + 256*fSS)
FJSRQQ EQU 256*(((1 shl 6) or (fESCAPE and 03Fh)) - fESCAPE)
FICRQQ EQU (fINT + 256*(BEGINT + 8)) - (fFWAIT + 256*fCS)
FJCRQQ EQU 256*(((2 shl 6) or (fESCAPE and 03Fh)) - fESCAPE)
END

Binary file not shown.

Binary file not shown.

Binary file not shown.

View File

@ -0,0 +1,771 @@
"README.DOC" File
Release Notes for the MICROSOFT(R) QuickBASIC Compiler
Version 3.0 for IBM(R) Personal Computers
and Compatibles
(C) Copyright Microsoft Corporation, 1987
THIS FILE CONTAINS IMPORTANT INFORMATION CONCERNING VERSION 3.0 OF
THE MICROSOFT(R) QUICKBASIC COMPILER. PLEASE READ THE ENTIRE FILE
VERY CAREFULLY BEFORE USING YOUR QUICKBASIC PRODUCT.
This file is divided into three parts, as follows:
PART CONTENTS
1 Information about additions and changes to QuickBASIC
made after the manual was printed.
2 Additions and corrections to the QuickBASIC Compiler
Version 3.0 update document.
3 Additions and corrections to the QuickBASIC Compiler
Version 2.0 manual.
For information on corrections to the software from Version 2.0 to 3.0,
please refer to the UPDATE.DOC file on this disk.
===<Part 1: Additional Information>=========================================
1. Executing Command Buttons
In QuickBASIC 2, pressing ENTER always executed the command button
with the double outline (the default command), regardless of which
button was highlighted. To execute the command in the highlighted
button, you had to press SPACEBAR.
In QuickBASIC 2.01 and 3, this is no longer the case: pressing either
ENTER or SPACEBAR executes the highlighted button.
2. The QB.INI Initialization File
QB.INI is an initialization file that QuickBASIC uses to set both the
Options settings in the View menu and the Autosave command settings
in the File menu. Upon exiting QuickBASIC, if you have modified
any of the Options settings or the state of the File menu's Autosave
command, these changes are written to QB.INI. Note that QB.INI is
not supplied on any of the product disks. It is created only when
you change the Options or Autosave settings. If you use only the
default settings, QB.INI is never created.
When QB.INI is created, it is placed in the current directory. When
QuickBASIC starts, it looks for QB.INI in the current directory, then
in the locations specified by the PATH environment variable.
3. Source-File Line Termination
QuickBASIC requires a CR-LF (carriage return-line feed) sequence at the
end of each line. If only carriage returns are present, QuickBASIC reads
the first 255 characters only, and continues without producing an error
message. If only line feeds are present, QuickBASIC appears to read the
file correctly, but will in fact overlook the last character of each line.
If you use an editor that places only a CR or an LF at the end of a line,
you need to modify your source files so they have the correct sequence at
the end of each line. The following program examines the end of each line
in a BASIC source file and inserts a carriage return, line feed, or both, if
needed (the original contents are saved in a file with the extension ".BAK").
' Be sure to compile this program with the "On Error" (/e) and
' "Resume Next" (/x) options to turn on error trapping
DEFINT A-Z
CONST FALSE = 0, TRUE = NOT FALSE
CarReturn$ = CHR$(13)
LineFeed$ = CHR$(10)
DO
CLS
INPUT "File (.BAS): ", InpFile$
Extension = INSTR(InpFile$,".")
IF Extension > 0 THEN
InpFile$ = LEFT$(InpFile$,Extension-1)
END IF
ON ERROR GOTO Handler
NAME InpFile$ + ".BAS" AS InpFile$ + ".BAK"
OPEN InpFile$ + ".BAK" FOR INPUT AS #1
ON ERROR GOTO 0
OPEN InpFile$ + ".BAS" FOR OUTPUT AS #2
PrevCarReturn = False
DO UNTIL EOF(1)
FileChar$ = INPUT$(1, #1)
IF FileChar$ = CarReturn$ THEN
IF PrevCarReturn THEN FileChar$ = LineFeed$ + FileChar$
PrevCarReturn = True
ELSEIF FileChar$ = LineFeed$ THEN
IF NOT PrevCarReturn THEN FileChar$ = CarReturn$ + FileChar$
PrevCarReturn = False
ELSEIF PrevCarReturn THEN
PrevCarReturn = False
FileChar$ = LineFeed$ + FileChar$
END IF
PRINT #2, FileChar$;
LOOP
CLOSE
PRINT "Another file (Y/N)?"
More$ = INPUT$(1)
LOOP WHILE More$ = "y" OR More$ = "Y"
SYSTEM
Handler:
ErrNumber = ERR
IF ErrNumber = 53 THEN
CLS
PRINT "No such file. Enter new name."
INPUT "File (.BAS): ", InpFile$
RESUME
ELSEIF ErrNumber = 58 THEN
KILL InpFile$ + ".BAK"
RESUME
ELSE
ON ERROR GOTO 0
ERROR ErrNumber
END IF
4. Using CALL ABSOLUTE with In-Memory Compilation
ABSOLUTE is considered an external subroutine by the QuickBASIC compiler.
The assembly-language source for this subroutine is in the file
ABSOLUTE.ASM, which can be found on either of the disks labeled Disk 1 in
the QuickBASIC distribution package. ABSOLUTE.OBJ, an assembled version of
this subroutine suitable for inclusion in a user library with the BUILDLIB
utility, can be found on either of the disks labeled Disk 2 in the QuickBASIC
distribution package.
5. Compilation Errors
When an error is detected during compilation, code generation stops. This
allows for faster compilation, but has the side effect that some errors may
be reported that are not errors. When the original error is corrected,
these side-effect errors go away. For example, the statements
FOR I = 1
.
.
.
NEXT I
generate two errors, "Missing TO" and "NEXT without FOR". When
the FOR statement is changed to read "FOR I = 1 to 10", both errors
are corrected.
6. COMMAND.COM, the SHELL Statement and the Free Menu's Shell Command
QuickBASIC requires COMMAND.COM before it can execute either a SHELL
statement or the Shell command from the File menu. QuickBASIC looks
for COMMAND.COM first in the directory specified in the COMSPEC
environment variable, then in the current directory.
7. Using the SHELL Statement in a Subroutine
The SHELL statement does not compress memory. If not enough contiguous
memory is available, (for example, if many CHAIN statements have been
executed, or several dynamic arrays were allocated then erased), a SHELL
statement may fail with an "Out of memory" error message.
8. Using the SHELL Statement with DOS 2.X
If you are using a 2.X version of DOS, programs that contain SHELL
statements may not exit correctly. This is due to a known problem in DOS
2.X. The problem occurs when DOS reloads the transient portion of the
command processor into high memory.
To exit QuickBASIC after executing an in-memory program that contains
SHELL statements, when the program finishes running, choose Shell from the
File menu, then type "exit" at the DOS prompt.
When standalone executable programs exit, the message "Invalid COMMAND.COM"
may appear. If so, you must restart your system. If you compile using
BRUN30.EXE, in most cases the program exits properly.
Another solution is to upgrade your DOS version to 3.X.
9. Running Terminate-and-Stay-Resident Programs from the File Menu's
Shell Command
Do not run terminate-and-stay-resident programs while executing the Shell
command from the File menu. When a Shell command is executed, QuickBASIC
is compressed into the smallest memory possible. The terminate-and-stay-
resident program occupies memory required by QuickBASIC, making it
impossible to compile or run a program, or do anything that allocates
memory.
10. Changing Directories from the File Menu's Shell Command
If you change directories after executing the Shell command from the File
menu, this directory is the current directory when you return to QuickBASIC.
Subsequent Load commands use this as the default directory, and when you
quit QuickBASIC, you will be in this directory.
11. Using BRUN30.EXE with User Libraries
The run-time module BRUN30.EXE obtains the user library using the name
the program module was compiled with. All independently compiled program
modules to be linked together must be compiled with the same user library
using the same name; othewise, an error occurs at run time.
You cannot use BCOM30.LIB, the alternate run-time library, with user
libraries.
12. Using /l with Nonreferenced Libraries
User libraries specified with the /l option are pulled into the
executable file regardless of whether the program requires them.
13. The User-Library Search Path
If path information is provided with the qb command's /l option, as in
qb progname /l \src\lib\mylib.exe
no path search is performed. If the library is not in the specified location
an error occurs. If no path information is provided, the current directory
is searched, then the directory specified in the LIB environment variable.
14. Graphics-Mode Statements
A color-graphics adapter is required if you are using any of the following
statements:
CIRCLE PMAP
COLOR (screen modes 1-10) POINT
DRAW PRESET
GET (graphics) PSET
LINE PUT (graphics)
PAINT SCREEN (screen modes 1-10)
PALETTE VIEW
PCOPY WINDOW
15. EGA-Card Restrictions
The EGA card does not support the COLOR statement's border parameter. Using
the border parameter causes unpredictable results.
16. Program Capacity
Because the Debug option generates extra code, extremely large programs
that are compiled with the Debug option may exceed the memory limits of
your computer.
17. Object-File Size
Programs compiled with the Debug option (the default) create larger
object files than programs compiled without the Debug option.
18. Using the PEN Function When a Mouse Driver Is Present
The mouse driver intercepts the PEN function's BIOS calls and redirects
them to the mouse. If you don't want to use the mouse as a lightpen, call
mouse function 14 to disable the mouse's lightpen-emulation flag, which is
on by default. Mouse function 13 turns lightpen emulation back on. For
example, the following code turns mouse lightpen emulation off:
CALL MOUSE(14,0,0,0)
See your mouse manual for more information.
19. Editing Responses to the INPUT Statement
The input editor supplied with QuickBASIC is a line editor only. This
means you can move and edit only horizontally. Attempts to use the
UP, DOWN, PGUP and PGDN cursor keys produce a beep.
20. Disk-Error Messages
Whenever you get a disk-error message, such as "Write protect violation",
DO NOT change to a different disk before selecting "RETRY". If you want
to retry with a different disk, select the "Cancel" button, replace the
disk, and compile again.
===<Part 2: Corrections to the QuickBASIC Compiler Version 3.0 Update>=======
Page Correction
---- ----------
Update-25 The first sentence under "Viewing User-Library Source Code"
should be changed to read as follows:
QuickBASIC's debugger also lets you see the text of any BASIC
source file used to build the user library, provided the
source file was compiled with either the /d command-line option
or the Debug option in the Compile... dialog box. If a source
in the user library was compiled without these options, the
debugger displays the following message if you try to view the
file with the F6 command:
***** No Debug Information *****
Update-44 The following information on emulating the function of an
8087/80287 math coprocessor should be added to Section 4.2:
Programs using either the standard BRUN3087.LIB library
or the alternate BCOM3087.LIB library automatically use an
8087/80287 coprocessor at run time if one is installed.
However, you can override the use of the coprocessor and force
an application to emulate its function by setting the NO87
environment variable.
HOW TO SET THE NO87 ENVIRONMENT VARIABLE
----------------------------------------
EXAMPLES
--------
SET NO87=Use of coprocessor suppressed
SET NO87=<one or more spaces>
Both of the preceding examples force software emulation of
the 8087/80287 coprocessor, provided the application is
using BRUN3087.LIB or BCOM3087.LIB linked with EMULATOR.OBJ
(see the "COPROCESSOR/EMULATION USAGE TABLE" below for
more information on when NO87 forces emulation). The first
setting causes the message
Use of coprocessor suppressed
to appear on the screen when a program that uses an 8087
or 80287 is executed, and an 8087 or 80287 is present.
The second setting does not display a message.
To turn off forced emulation, set NO87 equal to a null, or
empty, value.
EXAMPLE
-------
SET NO87=
The preceding example turns off software emulation of
the 8087/80287. Note: no spaces follow the "equal" (=)
sign.
COPROCESSOR/EMULATION USAGE TABLE
---------------------------------
The following table shows the effects of setting the NO87
variable on applications using QB87:
+----------------------+-----------------------+
| Math Coprocessor | Math Coprocessor not |
| Present and NO87 Set | Present |
+--------------------+----------------------+-----------------------+
| | | |
| Application | Emulates | Emulates |
| using BRUN3087.EXE | coprocessor | coprocessor |
| | | |
+--------------------+----------------------+-----------------------+
| Application | | |
| compiled with /o, | Emulates | Emulates |
| and linked with | coprocessor | coprocessor |
| EMULATOR.OBJ | | |
+--------------------+----------------------+-----------------------+
| Application | | |
| compiled with /o, | Uses | Does not run |
| but not linked | coprocessor | |
| with EMULATOR.OBJ | | |
+--------------------+----------------------+-----------------------+
NOTES ON TABLE:
1) The entries under the "Math Coprocessor not Present"
heading are valid regardless of whether or not the
NO87 variable is set.
2) If an 8087/80287 coprocessor is present and either one
of the following conditions is true, the application
always uses the coprocessor:
a) The NO87 variable is not set.
b) Forced emulation has been turned off by setting
NO87 equal to a null value.
Update-45 The text under the "Effect" heading for CLS 1 should
be changed to read as follows:
...Previously, CLS 1 changed the screen only
after a VIEW statement was executed.
Also, add the following to the text for CLS 2:
See the reference entry for VIEW PRINT in the
Microsoft QuickBASIC Compiler manual for more
information on creating a text window.
===<Part 3: Corrections to the QuickBASIC Compiler Version 2.0 Manual>=======
Page Correction
---- ----------
61-63 Significant enhancements have been made to QuickBASIC's debugging
capabilities. See the discussion in Section 3, "Debugging Commands,"
of the "Microsoft QuickBASIC Compiler Version 3.0 Update," which
supersedes the discussion on pages 61-63 of the Version 2.0 manual.
71 In the syntax line at the bottom of the page, the "c:buffersize"
option should be preceded by a forward slash, as follows:
/c:buffersize
76 In the first paragraph after Figure 4.2, the sentence "If you
are in a subdirectory..." should state that the entry ".."
appears in the "upper-left corner", not the "upper-right".
78 Binary files cannot be loaded into QuickBASIC. The note in the
middle of the page should read:
QuickBASIC accepts only ASCII files. If you attempt to load a
binary file, you will get an error.
78 BASICA ASCII files containing explicit extended ASCII characters,
(graphics characters), are treated as binary files by QuickBASIC.
93 In Section 4.4.3.11, "Exe," it should be noted that the executable
files created using this method require the support of the BRUN30.EXE
run-time module in order to execute.
120 The first line of this example (DEFINT I-L) should be changed
to DEFINT I-S so as to execute correctly.
152 The stack is preset to 768 bytes, not 512.
160 The list of nonexecutable statements should also include the
CONST statement.
161 In the example under Section 9.2.2, there should not be an underscore
character (_) following the FIELD variable D$.
162 String constants can be ASCII characters in the range 32 to 126.
(127 is the DEL character)
172 In the discussion of "Overflow" and "Division by zero" errors, the
following paragraph should be added to item 1a:
If you are running a program from the QuickBASIC
user interface (editor) with the Debug option on,
and one of these errors occurs, the program ends
and the appropriate error message appears in the
dialog box at the bottom of the screen. You are
then returned to the editor, with the cursor
positioned on the line where the error occurred.
The following should also be added to item 2:
If you are running a program from the QuickBASIC
interface with the Debug option off, the program
still ends with the appropriate error message
displayed; however, when you are returned to the
editor, the cursor is positioned on the first line
of the program, rather than the offending line.
183 In Table 10.1, you should add the statements PEEK, POKE, and DEF SEG
to the column "May Require Modifying Interpreter Programs," since
the memory maps of the interpreter and the compiler are different.
For example, programs that read from or write to memory locations in
the RAM-resident portion of the interpreter do not work in the
compiler environment since the interpreter is not present.
188 In Section 10.3.2, the $INCLUDE metacommand, restriction 2) is in
error. Included files may contain END statements.
193 In Table 10.6, you should add the statements PEEK, POKE, and
DEF SEG, since the memory maps of the interpreter and the compiler
are different. For example, programs that read from or write to memory
locations in the RAM-resident portion of the interpreter do not work in
the compiler environment since the interpreter is not present.
200 In the Action section for the BLOAD command, it states that
BLOAD can take input from "any input device." This is not true,
as the BLOAD command does not take input from the "KYBD:" device.
222 The EGA card does not support the COLOR statement's border parameter.
If you have an EGA card installed on your system, using the border
parameter causes unpredictable results.
229 The list of nonexecutable statements should also include the
CONST and DATA statements.
232 The "VO1" variable in the third line from the bottom should be changed
to read as follows:
DENS=W/VOL
235 The last line in the example should be "LOCATE Y,X" not
"LOCATE X,Y".
265 The syntax for the ERASE statement should have a comma between
the array names, as shown here:
ERASE arrayname [,arrayname...]
275 In the FIELD statement's Example 2, the order of arguments is reversed
for all string-manipulation functions. The affected section of the
program should read as follows:
.
.
.
IF (ZCHECK$ > "85699" AND ZCHECK$ < "85801") THEN
INFO$ = PLIST$
PRINT LEFT$(INFO$,25)
PRINT MID$(INFO$,16,25)
PRINT RIGHT$(INFO$,17)
END IF
The FIELD statements in the two examples shown under Example 4 should
be changed to read as follows:
FIELD #1, RECLENGTH% AS OFFSET$, SIZE% AS A$(I%)
and
FIELD #1, 15 AS A$(1), 10 AS A$(2),..., 8 AS A$(14)
280 Change the first sentence at the top of the page to read as
follows:
The body of a FOR...NEXT loop is executed at least
once, unless one of the following conditions is true,
in which case the loop is not executed:
* Step size is positive, and <start> is greater
than <end>.
* Step size is negative, and <start> is less than
<end>.
283 In the FRE function example, the first line of the example should be
a $DYNAMIC metacommand, as follows:
' $DYNAMIC
PRINT "Before dimensioning arrays: " FRE(""),FRE(0),FRE(-1)
.
.
.
286 There is a missing parenthesis in the formula for computing the GET
graphics statement's array size. There should be three left parentheses
after the INT keyword, as follows:
4 + INT(((x2 - x1 +1) * bits-per-pixel + 7)/8) * ((y2 - y1) +1)
297 The two examples comparing the single-line and block forms of the
IF...THEN...ELSE statement should read as follows:
Example 1:
INPUT "Price = ",x
IF (x >= 10000) THEN DISC! = x * .25! ELSE _
IF (x < 10000) AND (x >= 5000) THEN DISC! = x * .2! ELSE _
IF (x < 5000) AND (x >= 1000) THEN DISC! = x * .1! ELSE _
DISC! = 0
IF DISC! = 0 THEN PRINT "No discount" ELSE _
PRINT "Discounted price = "; : PRINT USING "$$####.##";x - DISC!
Example 2:
INPUT "Price = ",x
IF (x >= 10000) THEN
DISC! = x * .25!
ELSEIF (x < 10000) AND (x >= 5000) THEN
DISC! = x * .2!
ELSEIF (x < 5000) AND (x >= 1000) THEN
DISC! = x * .1!
ELSE DISC! = 0
END IF
IF DISC! = 0 THEN
PRINT "No discount"
ELSE
PRINT "Discounted price = ";
PRINT USING "$$####.##";x - DISC!
END IF
313 The last sentence of the description of Example 2, after
the semicolon, should read: "The last line displays the new
soft-key values."
314 Since QB3 supports the Advanced 101-Key keyboard, the
function keys F11 and F12 can now be trapped. Trapping
of F11 can be controlled with KEY(30) {ON | OFF | STOP},
while trapping of F12 can be controlled with
KEY(31) {ON | OFF | STOP}.
315 The table listed on this page is incomplete. In addition to
the values listed, you must also take into account the state
of the NUM LOCK and CAPS LOCK keys. For NUM LOCK active you
should add the value &H20, and for CAPS LOCK active you should
add the value &H40 to the keyboard flag.
317 The second comment in the example program should read:
' DOWN key will now be trapped
Also, note this program traps only the CTRL-s (lowercase s) key
sequence. To trap CTRL-S (with a capital S), you need to deal with
capital letters produced by holding down the SHIFT key, as well as
capital letters produced when the CAPS-LOCK key is active, as shown
here:
KEY 16, CHR$(&H05) + CHR$(&H1F) ' Trap CTRL + SHIFT + s
KEY 17, CHR$(&H44) + CHR$(&H1F) ' Trap CTRL + CAPS-LOCK + s
KEY (16) ON
KEY (17) ON
ON KEY (16) GOSUB KEYTRAP
ON KEY (17) GOSUB KEYTRAP
325 The STEP option example requires a hyphen before the STEP keyword, as
follows:
LINE -STEP (10,5)
The phrase following the example should read:
"draws a line from (10,10) to the point with x-coordinate
10+10 and y-coordinate 10+5, or (20,15)."
327 The Action for LINE INPUT should read:
Inputs an entire line (up to 255 characters) to a string variable...
338 The Remark for LOF should read:
When a file is opened in any mode, LOF returns the size of the file in
bytes.
348 In the description of the example it should be noted that line 100
converts the single-precision variable AMT to a 4-byte string;
therefore, the field variable D$ needs to be defined as only a
4-byte string:
FIELD #1, 4 AS D$, 20 AS N$
353 Delete the last sentence on this page.
369 Add the following note concerning the ACCESS clause:
The ACCESS clause works in an OPEN statement only if you are using
versions of DOS that support networking (3.0 or later). In addition,
you must run the SHARE.EXE program (or the network startup program must
run it) to perform any locking operation. Earlier versions of DOS
return an "Advanced Feature" error if ACCESS is used with OPEN.
375 The second sentence under the Action heading for the LF option should be
changed to read:
When LF is specified, a line-feed character (0AH) is automatically sent
after each carriage-return character (0DH).
388 The last sentence in the REMARKS section should be deleted. The
argument to the PEEK statement should be a single-precision
variable in the range 0-1,048,575.
396 The variable in the first line of PLAY statement's Example 1 should be
SCALE$, not SCALES$:
SCALE$ = "CDEFGAB"
410 In the example, all references to the file STORINVENT should be changed
to INVENT.DAT. The file argument to both OPEN statements should be
the same file, INVENT.DAT.
418 The first entry in the "Arguments" column should be (x,y), not
(x1,y1).
420 Images cannot be scaled with the PUT graphics statement. Only one set
of x,y coordinates can be specified as arguments to PUT. All text
after "Because you can specify..." in the second paragraph, and all of
the following paragraph, should be ignored.
424 The second sentence in the Remarks section for the READ statement should
be changed to read as follows:
READ statements assign DATA-statement values to variables on a
one-to-one basis.
448 The text format for SCREEN 1 should be 40 X 25, and the text format
for SCREEN 2 should be 80 X 25.
The first line under the SCREEN 2 heading should be corrected to
read as follows:
* 640 x 200 pixel high-resolution graphics
452 The color range listed for SCREEN 2 should be 0 - 15, not 0 - 1.
Because the WIDTH statement in QuickBASIC 3 now lets you set the
number of lines displayed on the screen as well as the number of
columns, the information on legal video-page ranges in SCREEN 0
shown in Table 11.6 should be updated as follows:
WIDTH Statement Display/Adapter Legal Video-Page
Format Hardware Ranges
----------------------------------------------------------------
WIDTH 80,25 MDPA 0 only
CGA 0 - 3
EGA (64K) 0 - 3
EGA (128K - 256K) 0 - 7
WIDTH 40,25 CGA, EGA 0 - 7
----------------------------------------------------------------
WIDTH 80,43 EGA (64K) 0 - 1
EGA (128K - 256K) 0 - 3
WIDTH 40,43 EGA (64K) 0 - 3
EGA (128K - 256K) 0 - 7
----------------------------------------------------------------
NOTE: 43-line mode is valid only with an EGA adapter with its
switch set for an EGA display.
474 The example for the STR$ function should read as follows:
DEF FNNum$(X)
X$ = STR$(X)
LENGTH = LEN(X$)
IF LEFT$(X$,1) <> "-" THEN LENGTH = LENGTH - 1
FNNum$ = RIGHT$(X$,LENGTH)
END DEF
PRINT "Enter 0 to end."
DO
INPUT "Find cosine of: ",Num
IF Num THEN PRINT "COS(" FNNum$(Num) ") = " COS(Num)
LOOP WHILE Num <> 0
482 In the example, the input to the prompt "Pattern to be searched
for?" must be SUB (not "sub") in order to get the output shown.
525 Add CASE, CONST, DEBUG, DO, ELSEIF, LOOP, OFF, RANDOM, and SELECT
to the list of reserved words.
Delete the dollar-sign ($) character at the end of GOTO.
535 Batch files created for versions of QuickBASIC before 2.0 require
modification. In older batch files, "bascom" should be "qb".
536 If you are using a version of DOS earlier than 3.0, use the PATH command
instead of the SET command to define the PATH variable. Using SET under
earlier versions of DOS can cause the PATH variable to work incorrectly
for some path specifications containing lowercase letters.
546 & The stack is preset to 768 bytes, not 512.
547
566 The third bulleted remark ("A USR function...") should be deleted.
570 The explanation for the error message "Too many files" should read:
This error most commonly occurs when an attempt is made to open a
number of files that exceeds the limit set by the FILES= parameter in
the CONFIG.SYS file. It also occurs when the per-directory file limit
is exceeded by an attempt to create a new file with the SAVE or OPEN
statement. Refer to your DOS manual for the number of files permitted
in a directory.

View File

@ -0,0 +1,382 @@
' Microsoft RemLine- Line Number Removal Utility
' Copyright (C) Microsoft Corporation- 1985,1986
' REMLINE.BAS is a program to remove line numbers from Microsoft BASIC
' Programs. It removes only those line numbers that are not the object
' of a goto, gosub or if-then
'
' REMLINE is run by typing:
'
' REMLINE [<input file> [, <output file>]]
'
' where <input file> is any input file name and <output file> is
' is any output file name. If <output file> is not present
' the output goes to the console. If <output file>
' is present <input file> has to be present.
'
' It makes several assumptions about the program
' 1. Program is correct syntactically, and runs in an MS Interpreter.
' 2. 200 limit on referenced line numbers. If larger, change LineTable!
' declaration.
' 3. The first number encountered on a line is considered a line num-
' ber; thus some continuation lines (in a compiler specific
' construct) may not work correctly.
' 4. Remember that ERL assumes the existence of line numbers, so
' REMLINE should not be used on programs which depend on ERL.
DEFINT a - z
DIM SHARED KeyWordTable$( 8 )
DIM SHARED LineTable!( 400 )
DIM KeyWordCount, LineCount, Seps$
DIM KeyBoard, Console
DIM InputFile$, OutputFile$
'
' FNToUpper$ - Convert string to uppercase
' Description:
' This routine converts a string to uppercase. If already uppercase
' nothing is done. Returns a null string if input is null
' Input:
' InString$ - string to convert
' Output:
' FNToUpper$ - uppercase string
' Uses:
' AscChar - temp used to hold ASCII form of character
' LenInString - Length of input string
' IndexInstring - Current index into input string
Def FNToUpper$(InString$)
LenInString = len(InString$)
' Exit if input string is empty (null)
if (LenInString = 0) then FNToUpper$ = "" : Exit Def
for IndexInstring = 1 to LenInString
AscChar = asc(mid$(InString$, IndexInstring, 1))
' &hdf is special bit pattern that converts from lower to upper
if ((AscChar >= asc("a")) and (AscChar <= asc("z"))) then _
AscChar = AscChar and &hdf: _
mid$(InString$, IndexInstring, 1) = chr$(AscChar)
next IndexInString
FNToUpper$ = InString$
End Def
'
' FNStrSpn - Get the index of the first character within InString$ that is
' NOT one of the characters from Separater$
' Description:
' This routine will search the parameter string InString$ until it finds
' a character that is not part of the Separater string. This can be used
' with FNStrBrk to isolate strings within strings that are separated by
' blanks, comma etc. whatever is specified in Separater$. This is especially
' helpful in extracting parameters from the command line. See FNGetToken$
' for example of use.
'
' Input:
' InString$ = string to search
' Separater$ = string of Separater
'
' Output:
' FNStrSpn = index into InString$ if 0 then all character in Separater$
' are in InString$
' Uses:
' LenInString, LenSeprater = length parameter strings
' ChTemp$ = temp used for current character from InString$
' StartFound = Logical flag if search was successful
' IndexSeparater, IndexInString = current indices into parameter strings
'
Def FNStrSpn(InString$, Separater$)
LenInString = Len(InString$)
LenSeparater = Len(Separater$)
' Examine each character from InString$ to see if it is in Separater$
for IndexInString = 1 to LenInString
ChTemp$ = Mid$(InString$, IndexInString, 1)
StartFound = false
' search all of the Separaters to see of any equal this character
for IndexSeparater = 1 to LenSeparater
if (ChTemp$ = Mid$(Separater$, IndexSeparater, 1)) then _
goto NextChar
next IndexSeparater
' found a character not equal to one of the Separaters$
' exit from loops
StartFound = true
goto EndStrSpn
NextChar:
Next IndexInString
EndStrSpn:
if (StartFound) then _
FNStrSpn = IndexInString _
else FnStrSpn = 0
End Def
'
' FNStrBrk - finds the first occurance of any character in string2$ in
' string1$
' Description:
' This routine is the opposite to FNStrSpn. It finds the first occurance
' of one of the characters from String2$ within String$. It is used
' generally for search from specific strings within strings. See FNSeparater
' on use. See FNGetToken$ to see the routines in use.
'
' Input:
' string1$ = string to search for first occurance
' string2$ = string of characters to search for
' Output:
' FNStrBrk = index to character in string1$ of first occurance
'
' Uses:
' LenString1 = length parameter string
' ChTemp$ = temp used for current character from String1$
' IndexString1 = current indices into parameter string
'
Def FNStrBrk(String1$, String2$)
LenString1 = Len(String1$)
' Search String1$ until one of the characters from String2$ is found
' or run out of characters from String$2
for IndexString1 = 1 to LenString1
ChTemp$ = Mid$(String1$, IndexString1, 1)
if (instr(String2$, ChTemp$)) then _
StartFound = true: _
FNStrBrk = IndexString1: _
Exit Def
Next IndexString1
FnStrBrk = 0
End Def
'
' FNGetToken$ - Extract a token for a string.
' Description:
' This routine extracts tokens from strings. A token is a word that is
' surrounded by separaters, such as spaces or commas. It is usually the
' word of interest and examining sentences or commands. If the string
' to search for tokens "Search$" is null (.i.e "") then the last
' non-null string passed will be used. The allows for multiple calls
' to FNGetToken$ to move through the string. EG: the sequences of calls
' would be:
' token$ = FNGetToken$("token string, a short one", " ,")
' while (token$ <> "")
' print token$
' token$ = FNGetToken$("", " ,")
' wend
' This will return "token", "string", "a", "short", "one"
'
' Note that the token is returned as an Uppercase character string.
'
' Input:
' Search$ = string to search
' InSeps$ = String of Seps$
' Output:
' FNGetToken$ = next token
' Uses:
' TokenString$ = last non-null string passed as parameter (do not modify)
' TokenIndex2 = index to last separater (do not modify)
' TokenIndex1 = index to last token
'
def FNGetToken$(Search$, InSeps$)
' Null strings indicate use of last string used
' TokenString$ is set to last string if Search$ is not null
if (Search$ = "") then _
Search$ = TokenString$ _
else TokenIndex2 = 1: _
TokenString$ = Search$
' If last separater position is past end of search string then no more
' tokens can be in string, since searching is started from this position
' Exit with null return in this case
if (TokenIndex2 >= len(Search$)) then _
FNGetToken$ = "": Exit Def
' Section out a token from the search string. This is done by finding the
' start of a token then locating it's end by the start of separaters
TokenIndex1 = FNStrSpn(mid$(Search$, TokenIndex2, len(Search$)), InSeps$)
' If no more token bump to end of line so we move past current point
if (TokenIndex1 = 0) then _
TokenIndex1 = len(Search$): _
else TokenIndex1 = TokenIndex1 + TokenIndex2 - 1
TokenIndex2 = FNStrBrk(mid$(Search$, TokenIndex1, len(Search$)), InSeps$)
' If separater position (end of token) came back zero the token must be
' up against end of string. Set the separater position one past string
' length so that size of token computation is correct and next call
' with same string will return null for no more tokens
if (TokenIndex2 = 0) then _
TokenIndex2 = len(Search$) + 1 _
else TokenIndex2 = TokenIndex1 + TokenIndex2 - 1
' Cut out token from search string and convert to uppercase.
' It is converted to uppercase since string compares are case sensitive
FNGetToken$ = FNToUpper$(mid$(Search$,TokenIndex1,TokenIndex2 - TokenIndex1))
end def
'
' FNIsNumber - Checks to see if character a number or alpha
' Description:
' This routine returns true if character passed is in the range 0 - 9
' It returns false if not. It is used to tell wither a token is
' a number or alpha.
' Input:
' Char - character to check
' Output:
' FNIsNumber - true if within 0 - 9
'
def FNIsNumber(Char$)
if (Char$ = "") then _
FNIsNumber = false: _
else CharAsc = asc(Char$): _
FNIsNumber = ((CharAsc >= asc("0")) and (CharAsc <= asc("9")))
end def
'
' GetFileNames - Parses the input and output file names from command$
' Description:
' This routine retrieves the input and output file names. These should
' be separated by a comma with the input file name coming first.
' Input:
' Command$ - Command line
' true, false - logical flags
' Output:
' Console - flag if no output file
' InputFile$, OutputFile$ - Input/Output file name
'
sub GetFileNames static
shared Console, InputFile$, OutputFile$, Seps$, true, false
Console = false
if (Command$ = "") then
print " Microsoft RemLine: Line Number Removal Utility"
print " "
Input " Input Filename (return to terminate)";InputFile$
If inputfile$ = "" Then Exit Sub
Input " Output Filename (default is console:)";OutputFile$
if (OutputFile$ = "") then Console = true
CLS
ELSE
InputFile$ = FNGetToken$(Command$, Seps$)
OutputFile$ = FNGetToken$("", Seps$)
if (OutputFile$ = "") then Console = true
END IF
ExitGet:
end sub
'
' BuildTable - Build a table of line numbers that are references
' Description:
' This routine examines all of the text file looking for line numbers
' that are the object of goto, gosub etc. As each is found it is entered
' into a table of these line numbers. This table is used during a second
' pass at the source to remove all line numbers not in this list
' Input:
' KeyWordTable$ - array of keywords that have line number following them
' KeyWordCount - number of entries in KeyWordTable$
' Seps$ - current token Seps$
' true, false - true, false flags
' Output:
' LineTable! - table of referenced line numbers
' LineCount - number of lines in LineTable!
'
sub BuildTable static
shared KeyWordCount, Seps$, LineCount, false, true
WHILE NOT EOF( 1 )
LINE INPUT #1, inlin$
token$ = FNGetToken$(inlin$, Seps$)
WHILE (token$ <> "")
for KeyIndex = 0 to KeyWordCount
if (KeyWordTable$(KeyIndex) <> token$) then goto KeyNotFound
token$ = FNGetToken$("", Seps$)
' loop through looking for multiple lines in the case
' of a computed gosub or goto. A non-numeric will terminate
' search (another keyword etc.)
while (FNIsNumber(Left$(token$,1)))
LineCount = LineCount + 1
LineTable!(LineCount) = val(token$)
token$ = FNGetToken$("", Seps$)
if token$ <> "" then KeyIndex = 0
wend
KeyNotFound:
next KeyIndex
KeyFound:
token$ = FNGetToken$("", Seps$)
WEND
WEND
end Sub
'
' GenOutFile - Generate output file
' Description:
' This routine generates the output file removing the unreferenced line
' numbers.
' Input:
' LineTable! - Table of line numbers that are referenced
' LineCount - number of entries in LineTable!
' Seps$ - Separaters used between keywords
' Console - flags if output to file
' false, true - logical flags
'
sub GenOutFile static
shared false, true, Seps$, LineCount, Console
WHILE NOT EOF( 1 )
LINE INPUT #1, inlin$
if (inlin$ = "") then goto NoLine
token$ = FNGetToken$(inlin$, Seps$)
if (not FNIsNumber(Left$(token$,1))) then goto NoLine
Linenumber! = VAL(token$)
FoundNumber = false
for index = 1 to LineCount
if (Linenumber! = LineTable!(index)) then _
FoundNumber = true
next index
if (not FoundNumber) then _
mid$(inlin$,FNStrSpn(inlin$,Seps$),len(token$)) = space$(len(token$))
NoLine:
if (Console) then _
PRINT inlin$ _
else Print #2, inlin$
WEND
end sub
'
' initialize the system
'
SUB initsys STATIC
SHARED true, false, KeyWordCount, Seps$, KeyWordTable$()
Seps$ = " ,: ": true = -1: false = 0
RESTORE keydata 'keywords
' Initialize the keyword table. Keywords are recognized so that
' the difference between a line number and a numeric contstant can
' be determined
KeyWordCount = 0
READ KeyWord$
WHILE KeyWord$ <> ""
KeyWordCount = KeyWordCount + 1
KeyWordTable$( KeyWordCount ) = KeyWord$
READ KeyWord$
WEND
END SUB
' keyword search data
keydata:
DATA THEN, ELSE, GOSUB, GOTO, RESUME, RETURN, RESTORE, RUN, ""
main:
CALL initsys
CALL GetFileNames
if (InputFile$ = "") goto ExitMain
OPEN InputFile$ FOR INPUT AS 1
call BuildTable
CLOSE #1
OPEN InputFile$ FOR INPUT AS 1
if (not Console) then _
OPEN OutputFile$ FOR OUTPUT AS 2
call GenOutFile
CLOSE #1
ExitMain:
end

View 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"

Binary file not shown.

View File

@ -0,0 +1,8 @@
defint a-z
sub square(starta) static
for x = starta to (starta+5)
for y = (starta) to (starta+5)
locate x,y:print "*"
next y
next x
end sub

View File

@ -0,0 +1,12 @@
defint a-z
sub tri (startd) static
startrow=10:startcol=startd
for row = 0 to 10
locate startrow+row,startcol-row
for x = startcol - row to startcol+row
locate startrow+row,x
print "*"
next x
next row
end sub

View 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

View File

@ -0,0 +1,168 @@
"UPDATE.DOC" File
Update Notes for the MICROSOFT(R) QuickBASIC Compiler
Version 3.0 for IBM(R) Personal Computers
and Compatibles
(C) Copyright Microsoft Corporation, 1987
This file contains a list of corrections made to Microsoft(R) QuickBASIC
since the last release. See the README.DOC file for corrections to the
manual and enhancements made to the product. These enhancements include
error listing capability and IBM(R) Advanced 101-Key keyboard support.
(1) With an IBM CGA card, and your display in screen mode 0, the active
page parameter now works as it does in IBM BASICA and as it did in
QuickBASIC 1.x. That is, more than one active page is allowed.
(2) With an IBM EGA card, the active page is now reset correctly upon return
to the user interface after program execution.
(3) In the user interface, inserting a word deleted from the end of a line no
longer inserts two spaces following the word.
(4) Palettes are no longer reversed on a CGA display in screen mode 1.
(5) A program that accesses a user-library routine containing a RESUME NEXT
no longer locks up the system.
(6) Compiling a program from the command line no longer locks up the system
if the disk is full.
(7) Variables passed to user-library routines no longer produce spurious
"String space corrupt" or "Out of data" errors, nor do they generate
incorrect values.
(8) The interaction between CHAIN, SHELL, and the DEBUG and .EXE options no
longer causes problems.
(9) Passing strings in COMMON that were defined in a FIELD statement no longer
causes a problem.
(10) High-intensity colors are now options for the foreground color in the
View menu's Options... dialog box.
(11) If an invalid CIRCLE statement was followed by a valid CIRCLE statement,
sometimes both the valid and invalid statements generated
"Illegal function call" errors. This has been corrected.
(12) The compiler no longer has problems optimizing code written without
line numbers and compiled without the DEBUG option.
(13) A problem with function-key assignments giving spurious "String space
corrupt" and "String heap corrupt" errors has been corrected.
(14) If a loop contained a SHELL statement followed by an LPRINT statement,
the LPRINT would sometimes fail after multiple iterations. This has
been corrected.
(15) The PAINT statement no longer has problems painting figures in EGA
screen modes 7-10 when there is a gap of less than eight pixels between
figures and painting begins on a byte boundary.
(16) The BSAVE statement now returns the proper error message if there is
no space on the disk.
(17) The STOP statement has been corrected to set the error stack level
properly.
(18) The color of the screen is now restored properly after a COLOR statement.
(19) The LOCATE statement now properly handles the cursor.
(20) Variables from a QuickBASIC program compiled with the BRUN20 library
are now accessed properly after a CHAIN statement transfers control
to an assembly-language program.
(21) The SCREEN statement has been corrected so that the order of COLOR and
SCREEN statements no longer makes a difference.
(22) An error could occur when a program containing an ON...GOSUB statement
was compiled with the /w (event handling) option. This has been corrected.
(23) The INKEY$ statement now works properly after an error routine traps an
attempt to open a nonexistent file with the OPEN statement.
(24) After a character is printed in column 80 followed by a semi-colon, CSRLIN
now returns the next line, as it does in IBM BASICA.
(25) Memory is no longer lost when the CHAIN statement runs multiple programs.
(26) Calling a user-defined function (DEF FN) within an OPEN statement no
longer causes an error.
(27) Using the compiler's /w option and the EXIT statement within a batch
file no longer causes a problem when the batch file is run.
(28) Integer division with a denominator of zero no longer locks up the system.
(29) Several memory-management problems -- including string-space manipulation,
which in turn led to errors ranging from "String space corrupt" to a
system lock up -- have been corrected.
(30) The combination of the SOUND statement with an OPEN statement that
accesses the "SCRN:" device now works properly.
(31) Floating-point subtraction performed between two SOUND statements no
longer causes an "Illegal function call" error on the second SOUND
statement.
(32) A problem with the the substring form of the PLAY statement has been
corrected.
(33) Typing CTRL-PRTSC in response to an INPUT statement no longer results
in all characters typed being printed twice on the printer.
(34) Using a null string for a file name in an OPEN statement now gives the
same error message whether the file is opened for input or output.
(35) The VIEW PRINT and CLS statements now work properly together.
(36) KEY(<n>) ON and ON KEY(<n>) GOSUB <line> statements can now be in the
same FOR...NEXT loop and work properly
(37) A machine lock up could occur on an 80286 machine if a COMMON block had
a single-precision variable as its first argument, the next statement
modified the variable (as in "b=b+1"), and the program was compiled with
the /O switch. This problem has been corrected.
(38) When the Compile... screen was displayed, pressing the right direction
key, the spacebar, and the ENTER key in the Program box (in that order)
would result in an "Invalid file specification" error. This error could
not be corrected except by completely retyping the file name. This has
been corrected so that the cursor is placed at the end of the name,
allowing use of the BACKSPACE key to correct the input error.
(39) The PPRINT utility now handles the metacommand SKIP[ :n] correctly.
(40) The PPRINT utility now works properly with line lengths greater than
80 characers when output is directed to LPT1:.
(41) The editor could lock up if a CUT/COPY operation was attempted when
the mouse was used to select text and the area marked for selection
extended beyond the last line of code. This has been corrected.
(42) An "Input past end" error could occur when using BLOAD to retrieve a file
that contained a 1A hex character (Control-Z). This has been corrected.
(43) QuickBASIC can now correctly handle user libraries larger than 64K.
(44) A DRAW statement containing a string expression and a very complex drawing
string could generate an "Out of memory" error. This has been corrected.
(45) A directory specified in a $INCLUDE statement could not contain an
extension. This has been corrected.
(46) Addressing an array element using an invalid subscript, even with the
Debug (/d) option set, could produce spurious or misleading error
messages. This has been corrected.
(47) The program INT86.ASM has been corrected to work with VARPTR.
(48) If the WRITE# statement is used to store characters in a random-file
buffer (a variable defined in a FIELD statement), QuickBASIC now pads
the record with blanks, as stated in the entry for the "PUT Statement
(File I/O)" in the QuickBASIC reference manual.
(49) Local variables in a user library are no longer preserved across a CHAIN,
and no longer result in a "String space corrupt" error.

View File

@ -0,0 +1,3 @@
rem compile to .obj in the app then link like this:
ntvdm -c link %1,,%1,.\,nul.def

View File

@ -0,0 +1,14 @@
<HTML>
<HEAD>
<TITLE>QuickBASIC 3.0 - Information</TITLE>
</HEAD>
<BODY>
<PRE> Title: QuickBASIC 3.0
Credits: The QuickBASIC 3.0 database, Copyright (C) 1987 by
Peter Norton Computing, Inc., was written by Craig Stinson,
Burt Alperson, Brad Kingsbury, John Socha, and Peter Norton.
</PRE>
</BODY>
</HTML>

View File

@ -0,0 +1,31 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Menu</TITLE></HEAD>
<BODY>
<OL>
<H2><LI>BASIC</LI></H2><P>
<OL>
<H3><LI><A HREF="ng320.html">Language</H3></A></LI><P>
<H3><LI><A HREF="ng34ce6.html">Operators</H3></A></LI><P>
<H3><LI><A HREF="ng38448.html">Data Types</H3></A></LI><P>
<H3><LI><A HREF="ng386bd.html">Switches and Options</H3></A></LI><P>
<H3><LI><A HREF="ng3943b.html">Type Conversions</H3></A></LI><P>
<H3><LI><A HREF="ng39706.html">Reserved Words</H3></A></LI><P>
<H3><LI><A HREF="ng39d55.html">Runtime Errors</H3></A></LI><P>
</OL>
<H2><LI>Tables</LI></H2><P>
<OL>
<H3><LI><A HREF="ng3a3de.html">ASCII Chart</H3></A></LI><P>
<H3><LI><A HREF="ng3b7e3.html">Line-Drawing Chars</H3></A></LI><P>
<H3><LI><A HREF="ng3bb15.html">Special Characters</H3></A></LI><P>
<H3><LI><A HREF="ng3c223.html">Color Chart</H3></A></LI><P>
<H3><LI><A HREF="ng3c7f0.html">Keyboard Codes</H3></A></LI><P>
<H3><LI><A HREF="ng3f0fb.html">Credits</H3></A></LI><P>
</OL>
</OL>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,32 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ngff2b.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng10367.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>ERDEV Critical Error Code</B>
<U>y</U> = <B>ERDEV</B>
Returns the error status of a device error. The low-order byte will
contain the INT 24h error code. The high-order byte will contain the
bits 15, 14, 13, 3, 2, 1, and 0 of the device attribute word.
----------------------------------------------------------------------
<B>Notes:</B> ERDEV is a read-only variable.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng10367.html">ERDEV$</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,36 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng101c4.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng10563.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>ERDEV$ Device Causing Critical Error</B>
<U>s$</U> = <B>ERDEV$</B>
Returns the name of the device that has caused an INT 24h (critical
error).
----------------------------------------------------------------------
<B>Notes:</B> If the device is a character device, ERDEV$ returns the
eight-bit device name. If the device is a block device,
ERDEV$ returns a two-character string consisting of the
drive letter and a colon.
ERDEV$ is a read-only variable.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng101c4.html">ERDEV</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,40 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng10367.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng107b9.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>ERL Line Number of Most Recent Error</B>
<U>y</U> = <B>ERL</B>
Returns the program line number at which the most recent error
occurred.
----------------------------------------------------------------------
<B>Notes:</B> If an error occurs on an unnumbered program line, then ERL
returns the last line number before the program line that
caused the error. If no line numbers are used at all, ERL
returns 0.
If the error occurs in an unnumbered program line, ERL
returns the last line number before the label.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng107b9.html">ERR</A>
<A HREF="ng108e8.html">ERROR</A>
<A HREF="ng1ded6.html">ON ERROR</A>
<A HREF="ng2b195.html">RESUME</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,33 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng10563.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng108e8.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>ERR Error Number</B>
<U>y</U> = <B>ERR</B>
Returns the error number of the most recent runtime error.
----------------------------------------------------------------------
<B>Notes:</B> If no error has occurred, ERR returns 0.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng10563.html">ERL</A>
<A HREF="ng108e8.html">ERROR</A>
<A HREF="ng1ded6.html">ON ERROR</A>
<A HREF="ng2b195.html">RESUME</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,49 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng107b9.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng10c5d.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>ERROR Force Error</B>
<B>ERROR</B> <U>n</U>
Produces error number <U>n</U>.
<U>n</U> An integer expression in the range 0 to 255.
----------------------------------------------------------------------
<B>Notes:</B> If <U>n</U> is not one of BASIC's standard error numbers, and no
ON ERROR routine is in use, ERROR <U>n</U> stops program
execution and produces an "Unprintable error" error
message.
If an ON ERROR routine is in effect, an ERROR <U>n</U> statement
is trapped in the normal way, whether or not the number is
one of BASIC's error numbers.
If you are using a nonstandard error number, Microsoft
recommends that you use the highest available number, to
maintain compatibility with future releases of QuickBASIC.
This statement is provided as an aid in debugging error-
trapping routines.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng10563.html">ERL</A>
<A HREF="ng107b9.html">ERR</A>
<A HREF="ng1ded6.html">ON ERROR</A>
<A HREF="ng2b195.html">RESUME</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,38 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng108e8.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng10e75.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>EXIT Exit Multiline Function, Loop, or Subprogram</B>
<B>EXIT</B> {DEF | DO | FOR | SUB}
Exits a multiline function definition, a DO loop, a FOR loop, or a
subprogram.
----------------------------------------------------------------------
<B>Notes:</B> The construct definition is not ENDed by the EXIT
statement. An END statement is still required.
Premature exit from a nested DO or FOR loop transfers
control to the immediately enclosing loop.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ngc7f7.html">DEF FN</A>
<A HREF="nge1c2.html">DO</A>
<A HREF="ng11abb.html">FOR</A>
<A HREF="ng2fea2.html">SUB...END SUB</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,36 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng10c5d.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng1107b.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>EXP Exponent (Natural)</B>
<U>y</U> = <B>EXP</B>(<U>numexpr</U>)
Returns e (the base of natural logarithms) to the power of <U>numexpr</U>.
<U>numexpr</U> A numeric expression less than or equal to 88.02969.
----------------------------------------------------------------------
<B>Notes:</B> If <U>x</U> is a double-precision variable or constant, EXP is
calculated in double precision. Otherwise it is calculated
in single precision.
The value of e is approximately 2.718282.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng19695.html">LOG</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,63 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng10e75.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng11727.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>FIELD Allocate Space for Random File Variables</B>
<B>FIELD</B> [#]<U>filenum</U>, <U>fieldwidth</U> <B>AS</B> <U>stringvar</U> [,<U>fieldwidth</U> AS <U>stringvar</U>]...
Allocates storage for any number of string variables, each of
specified character width, to be used in conjunction with a specified
random file buffer.
<U>filenum</U> The number under which the file was OPENed.
<U>fieldwidth</U> The number of character positions to be allotted to
<U>stringvar</U>.
<U>stringvar</U> A string variable to be used for random access.
----------------------------------------------------------------------
<B>Notes:</B> Once the random file has been FIELDed, data may be
extracted from the random file buffer after a GET
statement or placed into the buffer in preparation for a
PUT statement.
A string variable defined by means of the FIELD statement
points to a specified position in the random file buffer.
It should not thereafter be used as an INPUT variable or
on the left side of an assignment statement. Doing either
of these things will point the variable name into the
string space and remove it from the file buffer.
Multiple field definitions for a given random file buffer
are permitted. Each new FIELD statement starts again at
the first character position of the buffer, and all FIELD
statements for a given random file are in effect
simultaneously. All FIELD definitions are removed when a
file is CLOSEd.
QuickBASIC resets all FIELDed variables to null when the
associated file is CLOSEd or RESET. (In interpreted BASIC,
such variables retain their last assigned values.)
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng127c8.html">GET (File I/O)</A>
<A HREF="ng1b48a.html">LSET</A>
<A HREF="ng298af.html">PUT (File I/O)</A>
<A HREF="ng2bce4.html">RSET</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,37 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng1107b.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng119e5.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>FILES Display File Directory</B>
<B>FILES</B> [<U>filespec</U>]
Displays a directory listing, including all filenames, the name of the
directory, and the amount of free space.
<U>filespec</U> A string expression that follows DOS file naming
conventions. Can contain the wild-card characters * and ?.
Defaults to *.*.
----------------------------------------------------------------------
<B>Notes:</B> If the <U>filespec</U> argument is omitted, FILES lists all the
files in the current directory.
No matter what the contents of <U>filespec</U>, the output of the
FILES statement always includes a header consisting of the
full pathname of the current directory.
</PRE>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,29 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng11727.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng11abb.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>FIX Truncate to Integer</B>
<U>y</U> = <B>FIX</B>(<U>numexpr</U>)
Truncates, without rounding, any numeric expression to an integer.
<U>numexpr</U> A numeric expression.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng75f2.html">CINT</A>
<A HREF="ng15fe6.html">INT</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,88 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng119e5.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng1250d.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>FOR Begin Definition of FOR/NEXT Loop</B>
<B>FOR</B> <U>counter</U> = <U>start</U> <B>TO</B> <U>end</U> [STEP <U>increment</U>]
.
. [<U>statements</U>]
.
[EXIT FOR]
<B>NEXT</B> [<U>counter</U> [,<U>counter</U>...]]
Begins the definition of a FOR/NEXT loop.
<U>counter</U> A numeric variable to be used as the loop counter. All
numeric types are allowed, but the loop executes fastest
if <U>counter</U> is an integer variable.
<U>start</U> A numeric expression; the starting value of <U>counter</U>.
<U>end</U> A numeric expression; the ending value of <U>counter</U>.
<U>increment</U> A numeric expression; the value by which <U>counter</U> is
incremented or decremented with each iteration of the
loop. Defaults to +1.
----------------------------------------------------------------------
<B>Notes:</B> BASIC begins processing of the FOR/NEXT block by setting
<U>counter</U> equal to <U>start</U>. Then, if <U>increment</U> is positive and
<U>counter</U> is not greater than <U>end</U>, the statements between
the FOR statement and the NEXT statement are executed.
When the NEXT statement is encountered, <U>counter</U> is
increased by <U>increment</U>, and the process is repeated.
Execution passes to the statement following the NEXT
statement if <U>counter</U> is greater than <U>end</U>.
If <U>increment</U> is negative, execution of the FOR/NEXT loop
is terminated whenever <U>counter</U> becomes less than <U>end</U>.
If <U>increment</U> is 0, execution of the FOR/NEXT loop
continues until Ctrl-Break is pressed (unless one of the
repeated instructions itself increments <U>counter</U>).
Note that changes made within the FOR/NEXT loop to <U>counter</U>
affect the number of times the loop instructions are
executed; changes made to <U>start</U>, <U>end</U>, and <U>increment</U>,
however, do not have this effect.
There must be one and only one NEXT statement for each FOR
statement. Inclusion of <U>counter</U> in the NEXT statement is
optional; if <U>counter</U> is omitted, its value is assumed to
be that of <U>counter</U> in the most recent FOR statement.
FOR/NEXT loops may be nested within one another. Each FOR
must be given a unique <U>counter</U> value and each nested FOR
must have its NEXT statement appear within the enclosing
FOR-NEXT block.
Nested loops that have a common termination point may use
a single NEXT statement with values of <U>counter</U> matching
the values for each FOR statement.
The loop is skipped completely if <U>start</U> is greater than
<U>end</U> and <U>increment</U> is positive, or <U>start</U> is less than <U>end</U>
and <U>increment</U> is negative.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="nge1c2.html">DO</A>
<A HREF="ng1982e.html">LOOP</A>
<A HREF="ng1ca3c.html">NEXT</A>
<A HREF="ng33204.html">WEND</A>
<A HREF="ng335b1.html">WHILE</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,35 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng11abb.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng127c8.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>FRE Available Memory</B>
<U>y</U> = <B>FRE</B>({<U>strexpr</U> | <U>numexpr</U>})
Returns the number of bytes available in QuickBASIC's string space;
optionally forces a defragmentation of the string space.
<U>strexpr</U> A dummy argument; the actual value is inconsequential.
FRE(<U>strexpr</U>) causes QuickBASIC to clean house on its
string data space, then report the amount of free space
available.
<U>numexpr</U> A dummy argument. If <U>numexpr</U> = -1, QuickBASIC reports the
size in bytes of the largest free LNA (large numeric
array) entry. If any other value is used, QuickBASIC omits
the housecleaning step and reports the amount of free
space available.
</PRE>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,45 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng1250d.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng12b5a.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>GET Read Random File into Buffer File I/O</B>
<B>GET</B> [#]<U>filenum</U> [,<U>recnum</U>]
Transfers a record from a specified random access file into the
associated random file buffer.
<U>filenum</U> The number under which the file was OPENed.
<U>recnum</U> A numeric expression in the range 1 to 16,777,215,
specifying the number of the record to be transferred.
Defaults to the next record, or record 1 (if no previous
record has been read).
----------------------------------------------------------------------
<B>Notes:</B> After a record has been transferred from disk to the
random file buffer, its data may be accessed via INPUT #,
LINE INPUT #, or references to variables defined in a
FIELD statement.
If the file associated with <U>filenum</U> is a communications
file, then <U>recnum</U> specifies the number of bytes to read.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng20da4.html">OPEN</A>
<A HREF="ng298af.html">PUT (File I/O)</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,64 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng127c8.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng13094.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>GET Read Points from Screen Graphics</B>
<B>GET</B> (<U>x1</U>,<U>y1</U>)-(<U>x2</U>,<U>y2</U>),<U>arrayname</U>
Copies attributes from a specified rectangle within the screen buffer
into a specified array.
<U>x1</U>,<U>y1</U> Upper left corner of the rectangle to be copied.
<U>x2</U>,<U>y2</U> Lower right corner of the rectangle to be copied.
<U>arrayname</U> The name of a numeric array.
----------------------------------------------------------------------
<B>Notes:</B> To determine how large the array must be, use the
following formula:
4+INT(((<U>x2</U>-<U>x1</U>+1)*<U>bitsperpixel</U>+7)/8)*((<U>y2</U>-<U>y1</U>)+1)
where <U>bitsperpixel</U> relates to screen mode as follows:
<U>Mode</U> <U>Bitsperpixel</U>
SCREEN 1 2
SCREEN 2 1
SCREEN 7 4
SCREEN 8 4
SCREEN 9 2 (EGA memory = 64K)
4 (EGA memory &gt; 64K)
SCREEN 10 2
The amount of memory allocated per array element is as
follows:
Integer: 2 bytes per element
Single-precision: 4 bytes per element
Double-precision: 8 bytes per element
The first two bytes returned by the GET statement indicate
the horizontal dimension of the screen rectangle, in bits;
the second two bytes indicate the vertical dimension. The
remainder of the data returned by GET are the attributes
for each pixel in the rectangle.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng29bbc.html">PUT (Graphics)</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,46 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng12b5a.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng13449.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>GOSUB Execute Subroutine</B>
<B>GOSUB</B> {<U>linenum1</U> | <U>linelabel1</U>}
.
. [<U>statements</U>]
.
<B>RETURN</B> [{<U>linenum2</U> | <U>linelabel2</U>}]
Causes program execution to branch to the specified line number or
line label; when the RETURN statement is encountered, execution
branches to the statement immediately following the most recent GOSUB
statement--or to a specified line number or line label.
----------------------------------------------------------------------
<B>Notes:</B> If RETURN <U>linenumber2</U> or <U>linelabel2</U> is used, the return
must be made to a statement in the calling routine--i.e.,
the main program or the subroutine from which the current
subroutine was called.
Subroutines may be called any number of times, from any
number of different points in a program. They may be
nested, and they may have multiple RETURN statements.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ngc7f7.html">DEF FN</A>
<A HREF="ng2b513.html">RETURN</A>
<A HREF="ng2fea2.html">SUB...END SUB</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,32 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng13094.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng135de.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>GOTO Unconditional Branch</B>
<B>GOTO</B> {<U>linenum</U> | <U>linelabel</U>}
Causes program execution to branch to a specified line.
----------------------------------------------------------------------
<B>Notes:</B> The target of the GOTO must be at the same program level.
That is, you cannot GOTO a subprogram, subroutine, or
multiline function definition.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng10c5d.html">EXIT</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,36 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng13449.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng137c6.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>HEX$ Hexadecimal Value, as String</B>
<U>s$</U> = <B>HEX$</B>(<U>numexpr</U>)
Returns, as a string, the hexadecimal value of its argument.
--------------------------------------------------------------------------
<U>numexpr</U> A numeric expression in the range -32768 to 32767.
<B>Notes:</B> If <U>numexpr</U> is negative, HEX$ returns a two's complement
value.
Any fractional portion of <U>numexpr</U> is rounded before
creation of the string.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng1d6a0.html">OCT$</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,89 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng135de.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng13f30.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>IF Conditional Branch</B>
1. Block syntax
<B>IF</B> <U>expression</U> <B>THEN</B>
<U>statement1</U>
[<U>statement2</U>]
.
.
.
[ELSEIF <U>expression</U> THEN
<U>statement10</U>
[<U>statement11</U>]
.
.
.
[ELSE
<U>statement15</U>
[<U>statement16</U>]]
.
.
.
<B>ENDIF</B>
2. Single-line syntax (three variants)
<B>IF</B> <U>expression</U> <B>THEN</B> <U>statement1</U> [ELSE <U>statement2</U>]
Causes QuickBASIC to make a decision based on the value of an
expression.
<U>expression</U> A numeric expression; 0 is equivalent to FALSE, while all
other values are equivalent to TRUE.
<U>statement</U> Any legal statement. The single-line mode's statement can
be just a line number or line label. This is equivalent
to a GOTO statement with the specified label.
----------------------------------------------------------------------
<B>Notes:</B> Each <U>expression</U> in the IF/ELSEIF construct is tested in
order. As soon as an <U>expression</U> is found to be TRUE, then
its corresponding statements are executed. If no
expressions are TRUE, then the statements following the
ELSE keyword are executed. If ELSE is not specified, then
execution continues with the statement following the ENDIF
or the single-line IF statement.
The only difference between QuickBASIC's one-line
construct and that of interpreted BASIC is that QuickBASIC
allows the use of labels as well as numbered lines.
In the block construct, the following rules apply:
IF, ELSE, ELSEIF, and ENDIF must all be the first
keywords on their respective lines.
THEN must be the last keyword on its line; if anything
other than a comment follows on the same line with
THEN, QuickBASIC thinks it's reading a single-line
IF/THEN/ELSE construct.
IF blocks may be nested.
Do not put a colon before the ELSE keyword.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng209fe.html">ON...GOTO</A>
<A HREF="ng20631.html">ON...GOSUB</A>
<A HREF="ng2d400.html">SELECT</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,46 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng137c6.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng141ee.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>IMP Implication Operator</B>
<B>exp1 IMP exp2</B>
IMP is a logical operator. BASIC converts each operand to an integer
(each operand must yield an integer in the range -32768 to 32767, or
else an Overflow error occurs), then performs a bitwise comparison of
the results, according to the truth table below:
<U>exp1</U><B> </B><U>exp2</U><B> </B><U>exp1 IMP exp2</U>
1 1 1
1 0 0
0 1 1
0 0 1
The result is an integer.
<U>exp1</U>,<U>exp2</U> Any expression that produces a numeric result. This
includes Boolean expressions, where a TRUE result is
evaluated as -1 and a FALSE result is evaluated as 0.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng5198.html">AND</A>
<A HREF="ngfc6d.html">EQV</A>
<A HREF="ng1d3c8.html">NOT</A>
<A HREF="ng2265a.html">OR</A>
<A HREF="ng34a1f.html">XOR</A>
<A HREF="ng34f34.html">Precedence</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,64 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng13f30.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng147de.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>INKEY$ Most Recent Character at Keyboard</B>
<U>s$</U> = <B>INKEY$</B>
Returns, without echo, the character most recently entered into the
keyboard buffer, or a null string if no character is pending.
----------------------------------------------------------------------
<B>Notes:</B> The system variable INKEY$ must be assigned to an ordinary
string variable before it can be used in a BASIC
statement.
If the most recent character is one of the 255 IBM ASCII
characters, INKEY$ returns that character only. If the
most recent character is a "special" character--a function
key or a cursor keypress, for example--INKEY$ returns a
two-byte string; the first byte is 00h, and the second
byte is the extended code corresponding to the key
pressed.
If a key defined with the KEY statement is pressed, then
INKEY$ will return with the sequence of characters mapped
to the key as if the characters had been entered
independently.
Cursor control keys, such as TAB and BACKSPACE, will be
returned to INKEY$ without processing (in "raw" mode).
The following keys have special functions and will not be
returned through INKEY$:
Ctrl-Break Terminates the program unless the
Keyboard break option in the
Options menu was turned off.
Ctrl-Alt-Del Resets the computer system.
Ctrl-NumLock Suspends the system.
Shift-PrtScrn Prints the current screen display.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng148c5.html">INPUT</A>
<A HREF="ng151dd.html">INPUT #</A>
<A HREF="ng157f1.html">INPUT$</A>
<A HREF="ng18196.html">LINE INPUT</A>
<A HREF="ng18562.html">LINE INPUT #</A>
<A HREF="ng3c7f0.html">Keyboard Codes</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,29 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng141ee.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng148c5.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>INP Read from an I/O Port</B>
<U>y</U> = <B>INP</B>(<U>port</U>)
Returns a byte from a specified I/O port.
<U>port</U> A numeric expression in the range 0 to 65535, specifying
the port to read.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng22914.html">OUT</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,85 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng147de.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng151dd.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>INPUT Get Input from Keyboard</B>
<B>INPUT</B>[;]["<U>prompt</U>" {; | ,}] <U>variable</U> [,<U>variable</U>]...
Assigns input from the keyboard to one or more string or numeric
variables.
; If a semicolon is included directly after the INPUT
keyword, QuickBASIC does not issue a carriage return/line
feed after receiving the user's input.
<U>prompt</U> A string constant supplying a prompt to guide the user.
<U>variable</U> The name of a variable (string or numeric) that will
receive input.
----------------------------------------------------------------------
<B>Notes:</B> A prompt may be included in the INPUT statement to guide
the user; if included, it must be a string constant,
enclosed within quote marks.
If a prompt is included, it must be followed by either a
semicolon or a comma (outside the quotes, before the first
variable name). If it's followed by a semicolon,
QuickBASIC displays a question mark after the prompt
string. If it's followed by a comma, QuickBASIC suppresses
the question mark.
If no prompt is included, QuickBASIC displays a question
mark.
If more than one variable is included in the INPUT
statement, the user must enter values for all variables,
separated by commas. If only one variable is included in
the INPUT statement, the user has the option of simply
pressing the Enter key; QuickBASIC interprets that action
as 0 (for numeric variables) or null (for string
variables).
If the user enters too few or too many values in response
to an INPUT statement, QuickBASIC displays a ?Redo from
Start error message; no values are assigned to variables
until satisfactory input is received.
If the user enters a comma in response to an INPUT
statement, BASIC displays a ?Redo from Start error
message. You can avoid this irritation by using LINE
INPUT, instead of INPUT.
Input for a string variable need not be enclosed in quote
marks. String input that is enclosed within quotes is
handled as though it were not (QuickBASIC ignores the
quotes).
Input to a numeric variable must be numeric.
Editing keystrokes are active during response to INPUT. To
receive such keystrokes as part of an input string, use
INKEY$.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng141ee.html">INKEY$</A>
<A HREF="ng151dd.html">INPUT #</A>
<A HREF="ng157f1.html">INPUT$</A>
<A HREF="ng18196.html">LINE INPUT</A>
<A HREF="ng18562.html">LINE INPUT #</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,62 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng148c5.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng157f1.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>INPUT # Get Input from Sequential File or Device</B>
<B>INPUT</B> <B>#</B><U>filenum</U>, <U>variable</U> [,<U>variable</U>]...
Receives input from a sequential file or device and assigns it to one
or more numeric or string variables.
<U>filenum</U> The number under which the input file was OPENed. It may
refer to a disk file, a communications file, or the
keyboard (KYBD:).
<U>variable</U> The name of a variable (string or numeric) that will
receive input.
----------------------------------------------------------------------
<B>Notes:</B> The input data must match in type the variable(s) in the
INPUT # statement.
String input need not be enclosed within quote marks,
unless it contains one or more line feeds or carriage
returns or a significant quote mark or comma.
When receiving string input, QuickBASIC looks for the
first character other than a space, line feed, or carriage
return. If that character is a quote mark, QuickBASIC
considers the string to be everything from the character
following the quote mark up to the next quote mark. If the
first character is not a quote mark, QuickBASIC terminates
the string when it encounters a line feed, a carriage
return, or a comma--or when it has received 255
characters.
When receiving numeric input, QuickBASIC ignores leading
carriage returns, line feeds, and spaces, and it
terminates the input when it encounters a carriage return,
a line feed, or a comma.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng141ee.html">INKEY$</A>
<A HREF="ng148c5.html">INPUT</A>
<A HREF="ng157f1.html">INPUT$</A>
<A HREF="ng18196.html">LINE INPUT</A>
<A HREF="ng18562.html">LINE INPUT #</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,50 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng151dd.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng15bed.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>INPUT$ Read Specified Number of Characters</B>
<B>INPUT$</B>(<U>n</U> [,[#]<U>filenum</U>])
Returns a specified number of characters from a specified sequential
file or device, or from the keyboard.
<U>n</U> The number of characters to be read. Must be in the range
1 to 255.
<U>filenum</U> The number under which the input file was OPENed. If
omitted, the characters are read from the standard input
device (the keyboard, by default). Characters input from
the keyboard are not echoed to the screen.
-----------------------------------------------------------------------
<B>Notes:</B> The INPUT$ function terminates when the specified number
of characters have been received. It is not necessary to
press Enter.
INPUT$ doesn't allow the inputting of certain special key
combinations (for example, function and cursor keys).
These keys will return CHR$(0). Use INKEY$ to get around
this limitation.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng141ee.html">INKEY$</A>
<A HREF="ng148c5.html">INPUT</A>
<A HREF="ng151dd.html">INPUT #</A>
<A HREF="ng18196.html">LINE INPUT</A>
<A HREF="ng18562.html">LINE INPUT #</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,46 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng157f1.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng15fe6.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>INSTR Find Substring</B>
<B>INSTR</B>([<U>start</U>,] <U>stringexp1</U>,<U>stringexp2</U>)
Returns the character position within a string at which a substring is
found.
<U>stringexp1</U> The string to be scanned.
<U>stringexp2</U> The substring to be searched for.
<U>start</U> A numeric expression in the range 1 to 255; an optional
offset from which to start searching.
----------------------------------------------------------------------
<B>Notes:</B> If <U>start</U> is specified, BASIC begins searching at the
character at offset <U>start</U> (The first character in the
string is at offset 1). Whether or not <U>start</U> is specified,
INSTR returns the position at which <U>stringexp2</U> is found--
relative to the first character in the string (not to
<U>start</U>).
If <U>stringexp1</U> is null or if <U>start</U> is greater than
LEN(<U>stringexp1</U>), INSTR returns 0.
If <U>stringexp2</U> is null, then INSTR returns 1 (if <U>start</U> was
specified, then INSTR returns <U>start</U>.
</PRE>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,35 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng15bed.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng161a8.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>INT Next Lower Integer</B>
<U>y</U> = <B>INT</B>(<U>numexpr</U>)
Returns the largest integer value less than its argument.
<U>numexpr</U> A numeric expression.
----------------------------------------------------------------------
<B>Notes:</B> INT rounds everything down to the next lowest integer.
Compare this with CINT, which rounds in the conventional
manner, and FIX, which simply truncates.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng75f2.html">CINT</A>
<A HREF="ng119e5.html">FIX</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,32 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng15fe6.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng16339.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>IOCTL Send Control String to Device Driver</B>
<B>IOCTL</B>[#]<U>filenum</U>,<U>stringexpr</U>
Sends a command string of up to 255 characters to a specified device
driver.
<U>filenum</U> The number under which the device driver was OPENed.
<U>stringexpr</U> A string expression of up to 255 characters; can include
multiple commands separated by semicolons.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng16339.html">IOCTL$</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,28 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng161a8.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng16438.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>IOCTL$ Read Control String from Device Driver</B>
<U>s$</U> = <B>IOCTL$</B>([#]<U>filenum</U>)
Reads a control string from a specified device driver.
<U>filenum</U> The number under which the device driver was OPENed.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng161a8.html">IOCTL</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,81 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng16339.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng16dd7.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>KEY Set or Display Soft Keys</B>
<B>KEY</B> {ON | OFF | LIST}
<B>KEY</B> <U>n</U>, <U>strexpr</U>
<B>KEY</B> <U>n</U>, CHR$(<U>KBflag</U>) + CHR$(<U>scancode</U>)
Controls the display and contents of the function keys F1 through F10;
allows trapping of any scan code in any shift state.
ON KEY ON enables the display, on line 25, of current
function key settings. Only the first six character
assigned to each function key are displayed. If the screen
is in an 80-column display mode, all ten function keys are
displayed; if it's in a 40-column mode, the first five are
displayed. KEY ON is the default setting in BASIC.
OFF KEY OFF removes the function key display from line 25,
making line 25 available for other purposes. With KEY OFF
in effect, a LOCATE 25,<U>n</U> can be used to display other text
at the bottom of the screen. Line 25 does not scroll, but
it is erased by a CLS statement.
LIST KEY LIST displays the current soft key definitions on
screen.
<U>n</U>, <U>strexpr</U> KEY <U>n</U>, <U>strexpr</U> assigns the string expression <U>strexpr</U> to
function key <U>n</U>. <U>n</U> is a numeric expression in the range 1
to 10. Only the first 15 characters of <U>strexpr</U> are
significant. A null string <U>strexpr</U> deactivates the
associated function key.
<U>n</U>, CHR$(<U>KBflag</U>) + CHR$(<U>scancode</U>)
The statement KEY <U>n</U>, CHR$(<U>KBflag</U>) + CHR$(<U>scancode</U>) enables
your program to trap specified Ctrl keys, Alt keys, and
Shifted keys. <U>n</U> is a numeric expression in the range 15 to
20 (up to six traps may be in effect at once). <U>KBflag</U>,
which must be expressed in hexadecimal, specifies the
shift state of the key to be trapped, and scancode
specifies which alphanumeric key is to be trapped.
The following options are available for <U>KBflag</U>:
&amp;H40 Caps Lock active
&amp;H20 Num Lock active
&amp;H08 Alt key pressed
&amp;H04 Ctrl key pressed
&amp;H02 Left Shift key pressed
&amp;H01 Right Shift key pressed
&amp;H00 Caps Lock inactive, Num Lock inactive
These options may be used in additive fashion, to trap
combinations of shift states. For example,
CHR$(&amp;H08+&amp;H02+&amp;H01) would catch the combination of the
Alt key with either (or both) Shift keys.
Trapped keys do not enter the BIOS keyboard buffer.
Therefore, if either Ctrl-Break or Ctrl-Alt-Del is
trapped, there will be no way (other than powering down)
to break out of an infinite loop.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng16dd7.html">KEY(n)</A>
<A HREF="ng1e384.html">ON KEY</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,63 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng16438.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng17428.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>KEY(n) Enable/Disable Key Trapping</B>
<B>KEY</B>(<U>n</U>) {ON | OFF | STOP}
Enables or disables the trapping of a specified key via ON KEY(<U>n</U>).
<U>n</U> A numeric expression in the range 1 to 20, specifying the
key to trap, as follows:
1-10,30,31 Function keys F1 through F10, F11, F12
11 Cursor Up
12 Cursor Left
13 Cursor Right
14 Cursor Down
15-25 Keys defined via KEY <U>n</U>, CHR$(<U>KBflag</U>) +
CHR$(<U>scancode</U>)
ON KEY(<U>n</U>) ON activates trapping. If an ON KEY(<U>n</U>) GOSUB
statement has been executed, QuickBASIC checks before
executing each statement to see if the specified key has
been pressed. If it has, QuickBASIC performs the indicated
GOSUB.
OFF KEY(<U>n</U>) OFF deactivates trapping.
STOP KEY(<U>n</U>) STOP also deactivates trapping, but QuickBASIC
continues checking to see if the specified key has been
pressed. If it has been pressed, a subsequent KEY(<U>n</U>) ON
results in an immediate trap (provided an ON KEY(<U>n</U>)
statement with a nonzero line number has been executed).
-----------------------------------------------------------------------
<B>Notes:</B> If the "Checking Between Statements" option is in effect,
QB checks for communication activity after each statement.
If the "Event Trapping" option is selected, QB checks
after each new program line. If neither option is
selected, no trapping takes place.
For command-line compilation, /v enables checking after
each statement, and /w enables checking after each new
line. If neither switch is used, no trapping takes place.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng1e384.html">ON KEY</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,35 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng16dd7.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng175c1.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>KILL Delete File(s)</B>
<B>KILL</B> <U>filespec</U>
Deletes one or more files from disk.
<U>filespec</U> A string expression that follows DOS file naming
conventions.
-----------------------------------------------------------------------
<B>Notes:</B> Currently open files may not be deleted via KILL.
This command is equivalent to DOS's DEL (ERASE) command.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng2b8f2.html">RMDIR</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,32 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng17428.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng17755.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>LBOUND Lower Bound of Array Dimension</B>
<B>LBOUND</B>(<U>array</U>[,<U>dimension</U>])
Returns the lowest subscript for a given dimension of a given array.
<U>array</U> The name of an array.
<U>dimension</U> The number of a dimension. The first dimension of an array
is 1, the second is 2, and so on. For one-dimensional
arrays, this argument can be omitted.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng314eb.html">UBOUND</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,38 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng175c1.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng17947.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>LEFT$ Substring at Left</B>
<U>s$</U> = <B>LEFT$</B>(<U>stringexpr</U>,<U>n</U>)
Returns the leftmost <U>n</U> characters of a string.
<U>stringexpr</U> A string expression.
<U>n</U> A numeric expression in the range 0 to 32767.
----------------------------------------------------------------------
<B>Notes:</B> If <U>n</U> is larger than LEN(<U>stringepxr</U>), LEFT$ returns the
entire string.
If <U>n</U> is 0, LEFT$ returns a null string.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng1b754.html">MID$ (Function)</A>
<A HREF="ng2b724.html">RIGHT$</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,26 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng17755.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng17a25.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>LEN Length of String</B>
<U>y</U> = <B>LEN</B>(<U>stringexpr</U>)
Returns the number of characters in a string, including blanks and
nonprinting characters.
<U>stringexpr</U> A string expression.
</PRE>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,32 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng17947.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng17bbd.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>LET Assignment</B>
[<B>LET</B>] <U>variable</U> = <U>expression</U>
Assigns the value of an expression to a variable.
<U>variable</U> A valid variable name.
<U>expression</U> The value assigned to <U>variable</U>. <U>expression</U> and <U>variable</U>
must match in type.
----------------------------------------------------------------------
<B>Notes:</B> The keyword LET is optional.
</PRE>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,55 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng17a25.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng18196.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>LINE Draw Line or Box</B>
<B>LINE</B> [[STEP] (<U>x1</U>,<U>y1</U>)] - [STEP] (<U>x2</U>,<U>y2</U>) [,[<U>color</U>] [,B[F]]] [,<U>style</U>]
Draws a line or a box at specified coordinates, in a specified color.
STEP If included, coordinates are relative to last graphics
point referenced. If omitted, coordinates are absolute.
<U>x1</U>,<U>y1</U> If ,B option is used, <U>x1</U>,<U>y1</U> and <U>x2</U>,<U>y2</U> are corner
<U>x2</U>,<U>y2</U> coordinates of a rectangular box; otherwise <U>x1</U>,<U>y1</U> and
<U>x2</U>,<U>y2</U> are end points of a line.
<U>color</U> Specifies color to use . Defaults to 3 in medium
resolution, 1 in high resolution.
B Tells BASIC to draw a rectangular box instead of a line.
F Tells BASIC to fill the box.
<U>style</U> Allows you to draw a broken (dashed) line or box (see
below).
----------------------------------------------------------------------
<B>Notes:</B> If STEP is included with <U>x2</U>,<U>y2</U> but not <U>x1</U>,<U>y1</U>, then <U>x2</U> and
<U>y2</U> are measured relative to the absolute coordinate pair
(<U>x1</U>,<U>y1</U>).
QuickBASIC treats <U>style</U> as a 16-bit integer mask, plotting
the 1 bits and skipping the 0 bits, and repeating the
pattern as many times as necessary to create the specified
line. Thus a style value of 43690 (AAAAh,
1010101010101010b) would produce an evenly dotted line or
box, with every other pixel plotted. Note that QuickBASIC
ignores the "off" pixels; it does not plot them in the
background color.
</PRE>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,49 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng17bbd.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng18562.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>LINE INPUT Read Line from Keyboard, Ignoring Delimiters</B>
<B>LINE</B> <B>INPUT</B>[;]["<U>prompt</U>";] <U>stringvar</U>
Assigns a line of keyboard input (up to 255 characters) to a string
variable.
; If a semicolon is included directly after the INPUT
keyword, QuickBASIC does not issue a carriage return/line
feed after receiving the user's input.
<U>prompt</U> A string constant supplying a prompt to guide the user.
<U>stringvar</U> The name of a string variable that will receive input.
----------------------------------------------------------------------
<B>Notes:</B> LINE INPUT does not automatically display a question mark.
If you want a question mark, include it within a prompt
string.
Unlike INPUT, LINE INPUT ignores all delimiters.
Everything entered at the keyboard, including quote marks
and commas, is treated as part of the input string.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng141ee.html">INKEY$</A>
<A HREF="ng157f1.html">INPUT$</A>
<A HREF="ng148c5.html">INPUT</A>
<A HREF="ng151dd.html">INPUT #</A>
<A HREF="ng18562.html">LINE INPUT #</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,42 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng18196.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng18851.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>LINE INPUT# Read Line from File, Ignoring Delimiters</B>
<B>LINE</B> <B>INPUT</B> <B>#</B> <U>filenum</U>, <U>stringvar</U>
Assigns a line of input (up to 255 characters) from a sequential file
or device to a string variable.
<U>filenum</U> The number under which the file was opened.
<U>stringvar</U> The name of a string variable that will receive input.
----------------------------------------------------------------------
<B>Notes:</B> LINE INPUT # treats all commas and quote marks as part of
the input string. Input is terminated by a carriage
return-line feed pair (the carriage return and line feed
are included in the string variable assignment).
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng141ee.html">INKEY$</A>
<A HREF="ng157f1.html">INPUT$</A>
<A HREF="ng148c5.html">INPUT</A>
<A HREF="ng151dd.html">INPUT #</A>
<A HREF="ng18196.html">LINE INPUT</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,39 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng18562.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng18b5e.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>LOC Current File Position</B>
<U>y</U> = <B>LOC</B>(<U>filenum</U>)
Returns the record number last read from or written to a specified
(open) file.
<U>filenum</U> The number under which the file was OPENed.
----------------------------------------------------------------------
<B>Notes:</B> When a sequential file is opened for input, the first
sector is automatically read, so LOC(<U>filenum</U>) for a newly
opened sequential file returns 1. LOC(<U>filenum</U>) for a
sequential file opened for OUTPUT or APPEND returns the
current byte position divided by 128.
If <U>filenum</U> specifies a communications file, LOC returns
the number of characters waiting in the communications
buffer. If that number is larger than 255, LOC returns
255.
</PRE>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,58 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng18851.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng1905a.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>LOCATE Position the Cursor</B>
<B>LOCATE</B> [<U>row</U>][,[<U>col</U>][,[<U>cursor</U>][,[<U>start</U>][,<U>stop</U>]]]]
Sets the size and position of the cursor.
<U>row</U> A numeric expression in the range 1 to 25. Sets the row
position of the cursor.
<U>col</U> A numeric expression in the range 1 to 40 or 1 to 80. Sets
the column position of the cursor.
<U>cursor</U> A numeric expression. If 1, the cursor is visible; if 0,
the cursor is invisible.
<U>start</U> A numeric expression in the range 0 to 31. Sets the
starting scan line for the cursor.
<U>stop</U> A numeric expression in the range 0 to 31. Sets the ending
scan line for the cursor. If <U>start</U> is specified and <U>stop</U>
is not, <U>stop</U> assumes the value of <U>start</U>.
----------------------------------------------------------------------
<B>Notes:</B> Cursor scan lines are numbered from 0 (top) to 7 (CGA) or
13 (MDA).
If <U>stop</U> is less than <U>start</U>, a two-part (wraparound) cursor
results.
If the softkey display on line 25 has been turned off (via
KEY OFF), you may write to line 25 by means of LOCATE.
Line 25 does not scroll in any case.
Any argument to LOCATE may be omitted. Omitted arguments
retain former values.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ngb058.html">CSRLIN</A>
<A HREF="ng264a0.html">POS</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,52 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng18b5e.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng19504.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>LOCK Control File or Record Access</B>
<B>LOCK</B> [#] <U>filenum</U> [,{<U>record</U> | [<U>start</U>] TO <U>end</U>}]
.
. [<U>statements</U>]
.
UNLOCK [#] <U>filenum</U> [,{<U>record</U> | [<U>start</U>] TO <U>end</U>}]
Make a specified record range or an entire file inaccessible to other
users.
<U>filenum</U> The number under which the file was OPENed.
<U>record</U> The number of a record to be LOCKed or UNLOCKed.
<U>start</U> The number of the first record to be LOCKed or UNLOCKed.
<U>end</U> The number of the last record to be LOCKed or UNLOCKed.
-----------------------------------------------------------------------
<B>Notes:</B> If the file specified by <U>filenum</U> has been opened for
random access, you may lock either a single record number
(with the record argument) or a range of record numbers.
If you specify a range and omit the <U>start</U> argument, all
records from the beginning of the file to end are locked.
If the file specified by <U>filenum</U> was opened for sequential
input or output, the entire file is locked.
LOCK requires DOS 3.0 or later and SHARE.EXE.
It is important to UNLOCK all LOCKed records before
closing the file.
</PRE>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,30 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng1905a.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng19695.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>LOF Length of File</B>
<U>y</U> = <B>LOF</B>(<U>filenum</U>)
Returns the length, in bytes, of a specified file.
<U>filenum</U> The number under which the file was OPENed.
----------------------------------------------------------------------
<B>Notes:</B> If <U>filenum</U> specifies a communications file, LOF returns
the amount of free space in the communications buffer.
</PRE>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,34 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng19504.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng1982e.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>LOG Natural Logarithm</B>
<U>y</U> = <B>LOG</B>(<U>n</U>)
Returns the natural logarithm of a number.
<U>n</U> A numeric expression greater than 0.
-----------------------------------------------------------------------
<B>Notes:</B> If the argument is a double-precision value, LOG is
calculated in double precision; otherwise, it is
calculated in single precision.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng10e75.html">EXP</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,65 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng19695.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng19c46.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>LOOP End Definition of DO/LOOP Loop</B>
1. <B>DO</B>
.
. [statements]
.
.
[EXIT DO]
<B>LOOP</B> [{WHILE | UNTIL} <U>expression</U>]
2. <B>DO</B> [{WHILE | UNTIL} <U>expression</U>]
.
. [statements]
.
.
[EXIT DO]
<B>LOOP</B>
Ends the definition of a DO/LOOP loop.
<U>expression</U> A numeric expression. Nonzero values are equivalent to
TRUE, while zero values are equivalent to FALSE.
WHILE Causes execution of the loop as long as <U>expression</U> is
TRUE.
UNTIL Causes execution of the loop as long as <U>expression</U> is
FALSE.
EXIT DO An optional means to escape from the loop before its
termination.
LOOP Terminates the loop construct.
-----------------------------------------------------------------------
<B>Notes:</B> DO...LOOP is a general-purpose looping construct. The
optional termination test may be supplied at either the
beginning or the end. If no test is supplied, EXIT DO is
the only way to break out of the loop.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="nge1c2.html">DO</A>
<A HREF="ng11abb.html">FOR</A>
<A HREF="ng1ca3c.html">NEXT</A>
<A HREF="ng33204.html">WEND</A>
<A HREF="ng335b1.html">WHILE</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,32 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng1982e.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng19d58.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>LPOS Current Position of Print Head</B>
<U>y</U> = <B>LPOS</B>(<U>n</U>)
Returns the position of the print head within the printer buffer.
<U>n</U> Specifies the printer. The following values are allowed:
1 LPT1:
2 LPT2:
3 LPT3:
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng264a0.html">POS</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,60 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng19c46.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng1a3ba.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>LPRINT Output to LPT1:</B>
<B>LPRINT</B> [<U>exprlist</U>] [; | ,]
Prints one or more numeric or string expressions at LPT1:.
<U>exprlist</U> Numeric and/or string expressions to print. Each
expression must be separated from the one after it by
either a comma or a semicolon.
; If included at the end of the statement, suppresses the
usual carriage return and line feed.
----------------------------------------------------------------------
<B>Notes:</B> LPRINT with no argument sends a carriage return-line feed
pair.
QuickBASIC divides the output field into zones of 14
character positions. If an expression is followed by a
comma, QuickBASIC prints the next expression at the
beginning of the next zone. If an expression is followed
by a semicolon or space character, QuickBASIC prints the
next expression directly after the previous one.
If the last expression in the list to be displayed is
followed by a comma, a semicolon, SPC, or TAB, QuickBASIC
spaces appropriately and suppresses the carriage return-
line feed pair. Otherwise, QuickBASIC issues a carriage
return and line feed after executing an LPRINT statement.
QuickBASIC assumes a maximum line length of 80 characters,
unless a different value has been specified by means of a
WIDTH "LPT1:" statement. QuickBASIC sends a carriage
return-line feed pair when the maximum line length has
been reached. Therefore, for example, if you LPRINT an 80-
character string (and do not follow the string expression
with a semicolon), you will get two carriage return-line
feed pairs.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng2682a.html">PRINT</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,123 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng19d58.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng1b48a.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>LPRINT USING Formatted Output to LPT1:</B>
<B>LPRINT</B> <B>USING</B> <U>formatstr</U>; <U>exprlist</U> [; | ,]
Prints one or more string or numeric expressions, in a specified
format, at LPT1:.
<U>formatstr</U> A string variable or constant specifying the format in
which the data is to be printed (see below).
<U>exprlist</U> Numeric and/or string expressions to print. Each
expression must be separated from the one after it by
either a comma or a semicolon.
; If included at the end of the statement, suppresses the
usual carriage return and line feed.
<B>Formatting options:</B>
The following symbols may be used in <U>formatstr</U>:
<U>Symbol</U> <U>Meaning</U>
! Print only the first character of a string expression.
\ \ Print only the first <U>n</U> characters of a string expression,
where <U>n</U> is the number of spaces between the two
backslashes. If <U>n</U> is larger than the number of characters
in the string expression, BASIC pads the string expression
on the right with space characters.
&amp; Print a string expression without reformatting it.
. Specifies the position of the decimal point in a numeric
expression.
# A place-holder. If the numeric expression has more digits
to the right of the decimal point than the format string
has #s, BASIC rounds. If the numeric expression has more
digits to the left of the decimal point than the format
string has #s, BASIC prints all the digits to the left of
the decimal point and also prints a percent sign (%) to
the left of the number. If the numeric expression has
fewer digits to the left of the decimal point than the
format string has #s, BASIC right-justifies the number;
that is, it pads the number on the left with spaces. (But
if there are any #s to the left of the decimal point in
the format string, QuickBASIC always prints at least one
digit--a 0 if necessary--to the left of the decimal
point.)
+ Print a plus or minus sign, as appropriate, to the left of
the number. The sign is always printed immediately to the
left of the number.
- Print a minus sign immediately to the right of a negative
number (the minus sign should appear after the place
holders in the format string).
$$ Print a dollar sign immediately to the left of the number.
The double dollar sign also acts as a place holder for two
additional digits to the left of the decimal point, one of
which is the dollar sign itself. The dollar sign cannot be
prefixed to a number printed in exponential format.
** Fill any leading spaces with asterisks. The double
asterisk also acts as a place holder for two additional
digits to the left of the decimal point.
**$ Print a dollar sign immediately to the left of the number,
and fill any remaining leading spaces with asterisks. The
combination of two asterisks and a dollar sign also acts
as a place holder for three additional digits, one of
which is the dollar sign.
^^^^ Print a number in exponential format. The four carets
should appear after all place holders in the format
string.
_ Print next character as a literal. The combination _#, for
example, allows you to include a number sign as a literal
in your numeric format.
[other] Characters other than the foregoing may be included as
literals in the format string. Thus, for example, a single
dollar sign may be positioned to the left of a series of
place holders (#s) to achieve vertically aligned dollar
signs, and space characters may be placed at the right
side of the format string to achieve horizontal separation
between a series of numbers.
----------------------------------------------------------------------
<B>Notes:</B> QuickBASIC sends a carriage return-line feed pair after
the last expression to be printed, unless that expression
is followed by a semicolon.
QuickBASIC assumes a maximum line length of 80 characters,
unless a different value has been specified by means of a
WIDTH "LPT1:" statement. QuickBASIC sends a carriage
return-line feed pair when the maximum line length has
been reached.
Double-precision numbers in IEEE format may have three-
digit exponents. To print numbers with three-digit
exponents, use five carets instead of four.
</PRE>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,42 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng1a3ba.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng1b754.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>LSET Left-Justify Data in Field Variable</B>
<B>LSET</B> <U>fieldvar</U> = <U>stringexpr</U>
Left-justifies string data in a specified field of the random buffer,
in preparation for a PUT statement. Or left-justifies string data in
an ordinary string variable.
<U>fieldvar</U> A valid string variable name; specifies the variable into
which <U>stringexpr</U> is to be left-justified.
<U>stringexpr</U> A string expression.
----------------------------------------------------------------------
<B>Notes:</B> If LEN(<U>stringexpr</U>) is less than LEN(<U>fieldvar</U>), <U>fieldvar</U> is
padded on the right with space characters.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng1bf7e.html">MKD$</A>
<A HREF="ng1c304.html">MKI$</A>
<A HREF="ng1c42b.html">MKS$</A>
<A HREF="ng298af.html">PUT (File I/O)</A>
<A HREF="ng2bce4.html">RSET</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,45 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng1b48a.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng1ba73.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>MID$ Substring in Middle Function</B>
<U>s$</U> = <B>MID$</B>(<U>stringexpr</U>,<U>n</U>[,<U>length</U>])
Returns a specified number of characters from a specified string,
beginning at a specified character position.
<U>stringexpr</U> A string expression.
<U>n</U> A numeric expression in the range 1 to 32767;, specifies
the character position from which the substring is to be
extracted.
<U>length</U> A numeric expression in the range 0 to 32767; specifies
the number of characters to return.
----------------------------------------------------------------------
<B>Notes:</B> If length is omitted, MID$ returns all the characters in
the string beginning at character <U>n</U>.
MID$ may also be used as a statement.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng17755.html">LEFT$</A>
<A HREF="ng1ba73.html">MID$ (Statement)</A>
<A HREF="ng2b724.html">RIGHT$</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,53 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng1b754.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng1bf7e.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>MID$ Assign Substring Statement</B>
<B>MID$(</B><U>stringvar</U>,<U>n</U>[,length]) = <U>stringexpr</U>
Assigns all or some of a string expression to a string variable,
beginning at a specified character position within the string
variable.
<U>stringvar</U> The string variable whose characters will be replaced.
<U>n</U> A numeric expression in the range 1 to 255, specifying the
position within <U>stringvar</U> where the character replacement
is to begin.
length A numeric expression in the range 0 to 255, specifying the
number of characters from <U>stringexpr</U> that will be used. If
<U>length</U> is omitted, all of <U>stringexpr</U> is used.
<U>stringexpr</U> The string expression supplying replacement characters for
<U>stringvar</U>.
----------------------------------------------------------------------
<B>Notes:</B> In the syntax shown above, the characters in <U>stringexpr</U>
replace length characters in <U>stringvar</U>, beginning at
character <U>n</U>.
In no case will the length of <U>stringvar</U> increase as a
result of a MID$ statement. For example, if <U>stringvar</U> is
seven characters long, and <U>n</U> is 3 and length is 6, only
the first five characters of <U>stringexpr</U> will be assigned
to <U>stringvar</U>.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng1b754.html">MID$ (Function)</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,33 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng1ba73.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng1c0c5.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>MKD$ Convert Double-Precision to String</B>
<U>s$</U> = <B>MKD$</B>(<U>doubleexpr</U>)
Converts a double-precision expression into an 8-byte string, so that
it may be LSET or RSET into a random file buffer.
<U>doubleexpr</U> A double-precision expression.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ngb1c8.html">CVD</A>
<A HREF="ngb793.html">CVI</A>
<A HREF="ngb980.html">CVS</A>
<A HREF="ng1c304.html">MKI$</A>
<A HREF="ng1c42b.html">MKS$</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,30 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng1bf7e.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng1c1bb.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>MKDIR Create Subdirectory</B>
<B>MKDIR</B> <U>pathname</U>
Creates a new subdirectory.
<U>pathname</U> A string expression, of 128 or fewer characters, that
follows DOS path naming conventions.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng7372.html">CHDIR</A>
<A HREF="ng2b8f2.html">RMDIR</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,27 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng1c0c5.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng1c304.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>MKDMBF$ IEEE Double-Precision to MBF String QB87 only</B>
<B>MKDMBF$</B>(<U>doubleexpr</U>)
Converts a IEEE-format double-precision expression into an 8-byte
Microsoft Binary Format string, so that it may be LSET or RSET into a
random file buffer.
<U>doubleexpr</U> A double-precision expression.
</PRE>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,33 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng1c1bb.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng1c42b.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>MKI$ Convert Integer to String</B>
<U>s$</U> = <B>MKI$</B>(<U>intexpr</U>)
Converts an integer expression into a 2-byte string, so that it may be
LSET or RSET into a random file buffer.
<U>intexpr</U> An integer expression.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ngb1c8.html">CVD</A>
<A HREF="ngb793.html">CVI</A>
<A HREF="ngb980.html">CVS</A>
<A HREF="ng1bf7e.html">MKD$</A>
<A HREF="ng1c42b.html">MKS$</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,33 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng1c304.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng1c568.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>MKS$ Convert Single-Precision to String</B>
<B>MKS$</B>(<U>singleexpr</U>)
Converts a single-precision expression into a 4-byte string, so that
it may be LSET or RSET into a random file buffer.
<U>singleexpr</U> A single-precision expression.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ngb1c8.html">CVD</A>
<A HREF="ngb793.html">CVI</A>
<A HREF="ngb980.html">CVS</A>
<A HREF="ng1bf7e.html">MKD$</A>
<A HREF="ng1c304.html">MKI$</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,27 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng1c42b.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng1c6b1.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>MKSMBF$ IEEE Single-Precision to MBF String QB87 only</B>
<B>MKDMBF$</B>(<U>singleexpr</U>)
Converts a IEEE-format double-precision expression into an 8-byte
Microsoft Binary Format string, so that it may be LSET or RSET into a
random file buffer.
<U>singleexpr</U> A single-precision expression.
</PRE>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,36 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng1c568.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng1c816.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>MOD Modulo Arithmetic Operator</B>
<B>exp1 MOD exp2</B>
The MOD operator performs modulo arithmetic. That is, it performs an
integer division on its two operands (see \) and returns the
remainder. The result is an integer.
<U>exp1</U>,<U>exp2</U> Any numeric expression.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="ng4642.html">^^</A>
<A HREF="ng2ac8.html">-</A>
<A HREF="ng267b.html">*</A>
<A HREF="ng2d59.html">/</A>
<A HREF="ng447e.html">\</A>
<A HREF="ng282a.html">+</A>
<A HREF="ng34f34.html">Precedence</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,35 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng1c6b1.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng1ca3c.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>NAME Rename File</B>
<B>NAME</B> <U>oldname</U> <B>AS</B> <U>newname</U>
Renames a disk file.
<U>oldname</U> A string expression following the DOS file-naming
conventions. Must name an existing file.
<U>newname</U> A string expression following the DOS file-naming
conventions. May not name an existing file.
-----------------------------------------------------------------------
<B>Notes:</B> A file may be moved from one directory to another as a
result of NAME, but it may not be moved from one disk to
another.
</PRE>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

View File

@ -0,0 +1,84 @@
<HTML>
<HEAD><TITLE>QuickBASIC 3.0 - Long Entry</TITLE></HEAD>
<BODY>
<A HREF="ng1c816.html">[&lt;&lt;Previous Entry]</A>
<A HREF="ng320.html">[^^Up^^]</A>
<A HREF="ng1d3c8.html">[Next Entry&gt;&gt;]</A>
<A HREF="menu.html" >[Menu]</A>
<A HREF="info.html">[About The Guide]</A>
<HR>
<PRE>
<B>NEXT End Definition of FOR/NEXT Loop</B>
<B>FOR</B> counter = <U>start</U> <B>TO</B> <U>end</U> [STEP <U>increment</U>]
.
. [<U>statements</U>]
.
<B>NEXT</B> [<U>counter</U> [,<U>counter</U>...]]
Terminates the definition of a FOR/NEXT loop.
<U>counter</U> A numeric variable to be used as the loop counter. All
numeric types are allowed, but the loop executes fastest
if counter is an integer variable.
<U>start</U> A numeric expression; the starting value of counter.
<U>end</U> A numeric expression; the ending value of counter.
<U>increment</U> A numeric expression; the value by which counter is
incremented or decremented with each iteration of the
loop. Defaults to +1.
----------------------------------------------------------------------
<B>Notes:</B> BASIC begins processing of the FOR/NEXT block by setting
<U>counter</U> equal to start. Then, if <U>increment</U> is positive and
<U>counter</U> is less than end, the statements between the FOR
statement and the NEXT statement are executed. When the
NEXT statement is encountered, <U>counter</U> is increased by
<U>increment</U>, and the process is repeated. Execution passes
to the statement following the NEXT statement if <U>counter</U>
is equal to or greater than end.
If <U>increment</U> is negative, execution of the FOR/NEXT loop
is terminated whenever <U>counter</U> becomes equal to or less
than end.
If <U>increment</U> is 0, execution of the FOR/NEXT loop
continues until Ctrl-Break is pressed (unless one of the
repeated instructions itself increments <U>counter</U>).
Note that changes made within the FOR/NEXT loop to <U>counter</U>
affect the number of times the loop instructions are
executed; changes made to <U>start</U>, <U>end</U>, and <U>increment</U>,
however, do not have this effect.
There must be one and only one NEXT statement for each FOR
statement. Inclusion of <U>counter</U> in the NEXT statement is
optional; if <U>counter</U> is omitted, its value is assumed to
be that of <U>counter</U> in the most recent FOR statement.
FOR/NEXT loops may be nested within one another. Each FOR
must be given a unique <U>counter</U> value and each nested FOR
must have its NEXT statement appear within the enclosing
FOR-NEXT block.
Nested loops that have a common termination point may use
a single NEXT statement with values of <U>counter</U> matching
the values for each FOR statement.
</PRE>
<HR>
<B>See Also:</B>
<A HREF="nge1c2.html">DO</A>
<A HREF="ng11abb.html">FOR</A>
<A HREF="ng1982e.html">LOOP</A>
<A HREF="ng33204.html">WEND</A>
<A HREF="ng335b1.html">WHILE</A>
<HR>
This page created by ng2html v1.05, the Norton guide to HTML conversion utility.
Written by <A HREF="http://www.acemake.com/hagbard">Dave Pearson</A>
<HR>
</BODY>
</HTML>

Some files were not shown because too many files have changed in this diff Show More