QuickBasic Summary
Computer Methods in Chemical Engineering
This is my "cheat sheet".
-------------------------------------------------------------------------------
' This is a comment
: ... separate BASIC statements on one line
_ ... placed at the end of the line to indicated that the statement
continues to the next line (with a blank space preceeding "_").
END ... end the main program (same as STOP in FORTRAN)
label: ... a name followed by a colon
BASIC uses double quotes (") to enclose a string; FORTRAN a single quote ('); matlab a single quote(').
-------------------------------------------------------------------------------
Declare Variable Type
Variable Types (type suffix)
variable$ ... character/string of adjustable length
variable% ... integer*2
-32,768 -- 32,767 in decimal (default)
i%=&h0 -- i%=&hFFFF in hexadecimal
i%=&o0 -- i%=&o177777 in octal
variable& ... integer*4 (double precision)
-2,147,483,648 -- 2,147,483,647
i&=&h0& -- i&=&hFFFFFFFF& in hexadecimal (The first "&" is the base; the second "&" is "double precision".)
i&=&o0& -- i&=037777777777& in octal
variable! ... real*4 (default; e.g., x! and x are treated as the same variable, but a! and a% are not.)
-3.4X10^38 -- 3.4X10^38 (~7 significant figures)
(Note "!" does not mean factorial. Ok in Excel macro, but not as formula in worksheet cells.)
variable# ... real*8 (double precision, VBA's default)
-1.7X10^308 -- 1.7X10^308 (~15 significant figures)
DEFINT a-z 'INTEGER ... integer (INTEGER*2)
DEFLNG a 'LONG ... double precision integer (INTEGER*4)
DEFSNG a 'SINGLE ... real (REAL*4)
DEFDBL a 'DOUBLE .,. double precision (REAL*8)
DEFSTR a 'STRING ... All variables beginning with "A" are strings,
unless specified otherwise by (%, &, !, or #)
Same as IMPLICIT in FORTRAN
declare variablename AS type ... general format
"declare" is one of the following:
DIM
COMMON
REDIM
SHARED
STATIC
"type" is one of the following:
INTEGER .. 2-byte integer
LONG .. 4-byte integer
SINGLE .. 4-byte real
DOUBLE .. 8-byte real
STRING .. character*(*)
STRING*n .. character*n
user-defined-type
ex. TYPE newtype ... define a newtype from existing types
a AS INTEGER
b AS STRING*30
END TYPE
DIM c AS newtype
DIM d (1 TO 5) AS newtype ... create array of newtype
i% = c.a ... how to access the element in a record
abc$ = c.b
i% = d(2).a ... access the element in a array record
abc$ = d(2).b
ex.
DIM i%(100) AS INTEGER
DIM i%(1 TO 100, -50 TO 50) AS INTEGER ... negative limits are allowable
DIM a!(100) AS SINGLE
DIM i% AS INTEGER ... DIM can be used to declare type for a non-array
DIM x AS newtype
DIM a AS STRING variable length string
DIM a AS STRING*10 fixed length string
DIM a$ AS STRING*10 ... no good (since a$ is a string of adjustable length)
ex.
COMMON SHARED a!, b!, n% ... same as common a, b, n in FORTRAN
but declared only once in the main program;
variable names extend to the entire module.
PUBLIC in VBA, declared once & extend to entire module
DIM SHARED a!, b!, n% ... same as common a, b, n in FORTRAN
ex. Share an array
common shared x(), y()
n=5.
dim x(n), y(n)
ARRAYS
Array variables do not necessarily have to be declared; compiler gives a warning.
The default lower bound in BASIC is 0 (not 1, as in Fortran, Matlab)!!
The default lower bound in of a RANGE variable in Excel VBA is 1 (not 0)!!
The default lower bound in of a RANGE variable in IE/himl VBA is 0!!
OPTION BASE 1 ... change the default lower bound to 1 to conform with FORTRAN or Matlab
Default is a row vector (rather than a column vector) in VBA; the shape is self-evident in worksheet
Excel's matrix functions (e.g., Application.Minverse) require all elements to be explicitly assigned (leaving blank does not default to 0 in worksheet or called from VBA) !
The dimension can be read first before DIM statement is issued.
DIM array(10) ... DIMENSION array(10) in FORTRAN
DIM array(10,20)
DIM array (1 TO 10) AS INTEGER
DIM x(1 TO 10), y(1 TO 10, 1 TO 5)
DIM x(n%+1)
CONST a$ = "hi", b$ = "class", c$="today" ... not a variable, cannot be varied, cannot be assigned another value later
CONST pi!=3.14
.. same as FORTRAN: DATA pi/3.14/
.. Pi() is predefined in Excel formula, but not predefined in VBA; access from VBA as Pi=WorksheetFunction.Pi()
CONST n=100 : DIM a(n) ... same as FORTRAN: parameter (n=100)
CONST n=1 ... n is treated as an integer by default, although the default is a real number in a pure expression e.g., n=1
CONST n=3! ... n is treated as a real number ("!" means real number, not factorial)
CONST n!=3 ... n is treated as a real number
n = 1 ... n is treated as a real number; default varibale type is real
CALL subroutine(1) ... 1 is passed as an integer in a subroutine/function
CALL subroutine(1!) ... 1 is passed as a real number
CALL subroutine(1.) ... 1 is passed as a real number
DATA 1., 0., 0., 0. ... same as in FORTRAN
FOR I = 1 TO 4 REAL x(4)
READ x(i) DATA x/1., 0., 0., 0./
NEXT
-------------------------------------------------------------------------------
QBasic Intrinsic Functions
Math Functions ...
ABS
ATN ... ATAN in FORTRAN
COS
EXP
LOG ... base e in VBA, base 10 in Excel formula (LN is base e in Excel formula)
LOG(x)/LOG(10) ... to return log10 in VBA
SGN returns -1 (negative), 0 (for 0) or 1 (positive)
SIN
SQR ... SQRT in Excel formula & FORTRAN
TAN
Other Functions ...
LEN(variable) ... returns the number of bytes required by a variable
LEN(string expression) ... returns the number of characters in a string
ASC("A") ... returns the ASCII code of "A";
same as FORTRAN: ICHAR('A')
CHR$(64) ... returns the character corresponding to ASCII 64;
same as FORTRAN: CHAR(64)
EOF(1) ... see if eof is reached in file/device #1 (true or false)
LOC(1) ... returns the number of bytes waiting in the input buffer
LOF(1) ... returns the number of bytes remaining in the output buffer
RSET ... right justify a string variable
LSET ... left justify a string variable
ex. LSET NewVariable$ = oldvariable$
LTRIM$ ... strip away leading spaces
ex. FOR i=1 to 5 ... produce x(1) = ???
i$ = LTRIM$(STR$(i)) x(2) = ???
PRINT "x("; i$; ") = "; :
INPUT "", x(i)
NEXT i
ex. FOR i=1 to 5 ... produce x(1) = ???
PRINT " a("; LTRIM$(STR$(i)); ")="; a(i)
NEXT i
RTRIM$ ... strip away trailing spaces
good for comparing fixed length and variable length strings
ex. IF RTRIM$(fixed$) = variable$ THEN ...
INSTR(string1$, string2$)
... returns the position in string1 where string2 is found
0 means no match
ex. string1$ = "hi, class"
string2$ = "class"
PRINT INSTR(string1$, string2) ... gives 5
INSTR(start_position%, string1$, string2$)
... returns the position in string1 where string2 is found
start searching for matching at start_position%
good for searching for multiple matching
LEFT$(string$, n%) ... return the leftmost n% characters from string$
ex. PRINT LEFT$("hi, class", 4) ... gives "hi, "
RIGHT$(string$, n%) ... return the rightmost n% characters from string$
ex. PRINT RIGHT$("hi, class", 4) ... gives "lass"
MID$(string$, start%, n%)
... return n% characters from string$, starting at start%
ex. PRINT MID$("hi, class", 5, 2) ... gives "cl"
MID$("hi, class", 1) = "H" ... replace the 1st character with "H"
gives "Hi, class"
MID$("hi, class", 2) = "Go" ... gives "Go, class"
STRING$(n%, string$) ... generate string$ n% times
ex. PRINT STRING$(20, "*")
STRING$(n%, code%) ... generate string$ n% times
ex. PRINT STRING$(20, 64)
SPACES$(n%) ... generate n% blank spaces
LCASE$(string$) ... convert to lower case; good for case insensitive comparison
UCASE$(string$) ... convert to upper case; good for case insensitive comparison
ex. DO
resp$ = INPUT$(1)
LOOP WHILE UCASE$(resp$) = "Y"
MKI$ ... convert an integer to string
ex. New$ = MKI$(i%)
MKS$ ... convert a real variable to string
ex. New$ = MKS$(x!)
STR$ ... convert to string
ex. a$ = STR$(45) ... gives "45"
a$ = STR$(i%)
VAL("45") ... gives 45 (an integer)
ex. i% = VAL("45")
i% = VAL(string$)
r! = VAL("1.2")
ex. trick to ensure that the type is correct
INPUT "enter n: ", n$ | n%=VAL(n$)
------------------------------------------------------------------------------
Concatenation
A$ = "hi,"
B$ = " class"
C$ = A$ + B$ --> gives "hi, class"
C$ = C$ + A$ --> Add one character at a time
Integer division
7/3 --> 2.33333
7\3 --> 2 (invalid in Excel worksheet, ok in VBA)
9.6\2.4 --> 5 (i.e., 10\2 because real numbers are round off before
operation is performed.)
Not very accurate (bugs?) 0.5\1 --> 0
but 1.5\1 --> 2
2.5\1 --> 2
3.5\1 --> 4
(Use int(x+0.5) to round off instead.)
7 MOD 3 --> 1 (invalid in Excel worksheet -- use mod(7,3) in worksheet; ok in VBA)
Precedence of Operations
same as FORTRAN
^ ... exponentiation; same as FORTRAN **
-x^2 means -(x^2) in VBA, but (-x)^2 in Excel formula!!
Assignment
same as FORTRAN
Logical Operators -- Boolean expression, condition
= ... .EQ. in FORTRAN
<> ... .NE.
> ... .GT.
< ... .LT.
>= ... .GE.
<= ... .LE.
0 ... .FALSE.
-1 ... .TRUE. (1 in Excel worksheet, -1 in VBA)
AND (AND(expression1,expression2) in Excel worksheet)
OR
NOT()
e.g. false = 0000000000000000 (an integer value of 0)
true = 1111111111111111 (an integer value of -1); true=1 in Excel worksheet!
true = or any nonzero value in condition testing, e.g., "if 1 then" or "if -1 then"
Variable type is the same as integer.
PRINT 1=1 ... gives -1
e.g., The following is very strange (in QBasic)!
TRUE = 1 FALSE=0
FALSE = NOT(TRUE) ... gives 0 in VBA TRUE = NOT (FALSE) ... gives -1 in VBA
... gives -2, not 0
ex. CONST FALSE = 0, TRUE = NOT FALSE ... good for readability or
imitating FORTRAN
... not valid in VBA, ok in qbasic
ex. Two strings can be compared based on ASCII values ... good for sorting
------------------------------------------------------------------------------
-------------------------------------------------------------------------------
CONDITION, FLOW CONTROL
ELSEIF and ELSE part are optional
IF condition1 THEN -+ ... same as FORTRAN: + IF (condition1) THEN
statement1 | | statement1
ELSEIF condition2 THEN | | ELSEIF (condition2) THEN
statement2 | | statement2
ELSEIF condition3 THEN | | ELSEIF (condition3) THEN
statement3 | | statement3
ELSE | | ELSE
statement4 | | statement4
END IF -+ + END IF
short version
IF condition THEN statement IF (condition) statement
??? How to break from if..endif??? matlab: break
------------------------------------------------------------------------------
SELECT CASE expression -+ ... same as FORTRAN:
CASE expression-list1 | + IF(expression .eq. expression-list1)THEN
statement1 | | statement1
CASE expression-list2 | | ELSEIF(expression .eq. expression-list2)THEN
statement2 | | statement2
: | | :
CASE ELSE | | ELSE
statement3 | | statement3
END SELECT -+ + ENDIF
Only the statements corresponding to the first match (not subsequent matches)
will be executed.
e.g. SELECT CASE i%
CASE 1, 3, 5, 7, j%, k%
PRINT "Odd"
CASE 2, 4, 6, 8
PRINT "even"
CASE ELSE
PRINT "Out of range"
END SELECT
e.g. SELECT CASE i%
CASE 1 TO 4, -4 TO -1 (must put the lesser value first)
statement
CASE IS >5
statement
END SELECT
e.g. CASE "abc" TO "bear" ... O.K.
CASE "abc" TO "Bear" ... no good (ASCII order is wrong)
e.g. CASE IShigh% ... multiple expressions
------------------------------------------------------------------------------
ON i% GOSUB 10, 20, 30, 40, 50
... goto 10 if i%=1, goto 20 if i%=2, goto 30 if i%=3 etc
... same as FORTRAN: GOTO (10, 20, 30, 40, 50) I
... unstructured; avoid
------------------------------------------------------------------------------
FOR i%=1 TO 5 + ... same as FORTRAN: + DO label icount=1, 5
statements | | statements
NEXT i% + + label CONTINUE
... The count variable may start with a negative integer.
... STEP other than 1 can be given.
... Infinite loop when STEP 0 is used. (This is not allowed in FORTRAN.)
FOR i%=5 TO 1 STEP -1 + ... same as FORTRAN: + DO label icount=5, 1, -1
statements | | statements
NEXT i% + + label CONTINUE
Forced exist from FOR ... NEXT loop
FOR i%=5 TO 1 STEP -1 + ... same as FORTRAN: + DO label icount=5, 1, -1
statements | | statements
EXIT FOR | | if( ... ) goto 101
statements | | statements
NEXT i% + + label CONTINUE
101 outside the loop
Counter is optional ...
ex. FOR count%=1 TO 5
statements
NEXT
Nesting ...
ex. FOR i%=1 TO 5
FOR j%=1 TO 10
statements
NEXT
NEXT
ex. FOR i%=1 TO 5
FOR j%=1 TO 10
statements
NEXT j%
NEXT i%
ex. FOR i%=1 TO 5
FOR j%=1 TO 10
statements
NEXT j%, i% (list the most inner counter first)
EXIT FOR is the equivalent of "BREAK"
There is NO equivalent of "CONTINUE" (i.e., skip to the end of the loop for the current iteration)
want (but VBA does not provide):
IF condition THEN CONTINUE
VBA.NET (which is not VBA in Office) provides "continue" statement
VBA implementation with GOTO (non-structured & not recommended):
FOR ...
:
IF contition THEN GOTO endloop
:
endloop:
NEXT
VBA implementation with structured programming by testing "NOT"
FOR ...
:
IF NOT contition THEN
:
END IF
NEXT
------------------------------------------------------------------------------
WHILE condition label IF (condition) THEN
statements statements
WEND ENDIF
GOTO label
------------------------------------------------------------------------------
Use EXIT DO within IF placed inside the loop to get out of the DO...LOOP
DO +
statements | infinite loop
IF .. THEN EXIT DO |
statements |
LOOP +
Test the condition first (thus, the statements in the loop may be completely skipped.)
DO WHILE condition + ... same as FORTRAN: + label IF (condition) THEN
statements | | statements
LOOP + | END IF
+ GOTO label
DO UNTIL condition + ... same as FORTRAN: + label IF (.not. condition) THEN
statements | | statements
LOOP + | END IF
+ GOTO label
Test the condition afterwards (thus, the statements in the loop are executed
at least once.)
DO +... same as FORTRAN: + label statements
statements | + IF (condition )GOTO label
LOOP WHILE condition+
DO +... same as FORTRAN: + label statements
statements | + IF (.not. condition)GOTO label
LOOP UNTIL condition+
------------------------------------------------------------------------------
INPUT/OUTPUT, FILES
PRINT (in QBasic, not VBA!)
PRINT A; B -- the 2nd item is separated from the 1st by a space.
(May show 2 spaces between numbers because there is also a
space before the positive number.)
PRINT A, B -- the 2nd item is printed at the next tab position
(multiples of 14).
PRINT "A"; B --- the 2nd item is separated from the 1st string by 0 space.
(May show 1 space between the string and the number because
there is a space before the positive number.)
PRINT A; + combine output of several PRINT statements on the same line.
PRINT B +
PRINT A, + combine output of several PRINT statements on the same line.
PRINT B +
PRINT ... no argument ... print a blank line
PRINT "character strings"
PRINT logical expression
PRINT USING "###.###"; A ... 123.456 same as F7.3
PRINT USING "$$###.##"; A ... $123.45 (note two $ signs so that the $ sign is next to the number)
PRINT USING "#.###^^^^"; A ... 0.123E+03 same as E9.3
PRINT USING "+###"; A ... +123
PRINT USING "##_! = factorial of ## = ##,###.##"; 10; 10; 123.44 ("_!" gives "!")
... 10! = factorial of 10 = 123.44
fmt$ = "##_! = factorial of ## = ##,###.##" + same as the last line
PRINT USING fmt$; 10; 10; 123.44 +
PRINT "x("; i$; ") = "; using "##.#####^^^^"; x(i)
PRINT using "##.#####^^^^"; a, b, c ... repeat the same format
PRINT "a"; SPC(10); "b" ... skip 10 spaces between "a" and "b"
PRINT "a"; TAB(10); "b" ... print "b" on column 10
Other Output Statements
CLS
LOCATE row, column
LOCATE row, column, cursor ... cursor=1 ... visible
cursor=0 ... invisible
LOCATE row, column, cursor, start, stop
... start,stop=0..7 or 13 ... cursor size
| +Ä mono
+Ä color
e.g. LOCATE ,, 1, 0, 7 ... fill the whole space
LOCATE ,, 1, 0, 3 ... fill the top half
LOCATE ,, 1, 4, 7 ... fill the bottom half
LOCATE ,, 1, 6, 2 ... split cursor
WIDTH columns, rows
columns ... 40, 80
rows ... 25, 30, 43, 50, 60
VIEW PRINT topline TO bottom line
... only the portion between topline and bottom line is scrolled
... Use "CLS 2" to clear the text window
INPUT variable1, variable2 ... prompt with "?"
INPUT "prompt"; variable1, variable2 ... propmt with "prompt?"
INPUT "prompt: ", variable1, variable2 ... prompt with "prompt: "
same as + PRINT "prompt: ";
+ INPUT "", variable1, variable2
INPUT; "1st: ", v1 + appear on the same line
INPUT "2nd: ", v2 +
Because "," is used to separate input fields, enclose a string
variable input in " " if it contains ","; otherwise, use LINE INPUT.
LINE INPUT uses the same rules as INPUT, except that each line ended
with "Enter" is treated as one item.
LINE INPUT variable1, variable2
LINE INPUT #1, variable1, variable2
ex. PRINT "enter n: ";
LINE INPUT n%
Other Input functions
PRINT INPUT$(5) ... wait for 5 key strokes
a$ = INPUT$(5) ... read 5 key strokes (read all characters)
a$ = INPUT$(5, #1) ... read 5 key strokes (read all characters)
from #1
DO: LOOP WHILE INKEY$ = "" ... wait for a key press
ex. trap extended key combinations (e.g., INS key = HEX 52 = DEC 82)
DO: a$ = INKEY$: LOOP WHILE a$ = "" OR LEN(a$) < 2:
IF ASC(MID$(a$,2))=82 THEN command
ex. trap extended key combinations (same as above)
IF a$=MKI$(&H5200) THEN command
irow% = CSRLIN ... get cursor position -- row number
icol% = POS(idummy%) ... get cursor position -- column number
comparison ...
INPUT ... "," is the delimiter
LINE INPUT ... is the delimiter
INPUT$() ... no delimiter
OPEN "filename" FOR OUPUT AS #1 ... same as open(1,file='filename',status='new')
(existing file will be written over -- Be careful!)
OPEN "filename" FOR APPEND AS #1 ... append existing file
OPEN "filename" FOR INPUT AS #1 ... same as open(1,file='filename',status='old')
OPEN "filename" FOR RANDOM AS #1 ... random acess file
OPEN "filename" FOR BINARY AS #1 ... binary file
CLOSE #1 ... same as FORTRAN close(1)
KILL filespec ... same as DOS' "del filespec"
NAME filename1 AS filename2 ... same as DOS' "rename filename1 filename2"
ex. Automatically find the next file number with FREEFILE function
OPEN "file1" FOR INPUT AS #1
n% = FREEFILE
OPEN "file2" FOR INPUT AS #n%
INPUT #1, variable list
WRITE #1, variable list ... string variables enclosed in " ",
and field separated by "," in the file
PRINT #1, variable list ... the same as what one will see on screen
try to use WRITE/INPUT combinations
There is no easy way to write '"'. Do the following
q$ = CHR$(34)
PRINT q$; a$; q$
Steps in using a random acess file
1. Define a new type, i.e., new record structure
TYPE newtype
variable1 AS INTEGER
variable2 AS STRING*30
variable3 AS SINGLE
END TYPE
2. Declare a variable of new type
DIM RecordVariable AS newtype
2. Define the length of each field in a file
FIELD #1, 2 AS variable1, 30 AS variable2, 4 AS variable3
3. Open a file
OPEN "filename" FOR RANDOM AS #1 LEN = LEN(RecordVariable)
or
OPEN "filename" FOR RANDOM AS #1 LEN = 36
... calculate the record length by hand
record% = LOF(1) \ LEN(RecordVariable)
... find the number of record in the file
4. Read from or write to file
GET #1, record%, RecordVariable
GET #1, , RecordVariable ... move to the next record
PUT #1, record%+1, RecordVariable
PUT #1, , RecordVariable ... move to the next record
5. Each field in the record variable can be accessed individually
a% = RecordVariable.variable1
a$ = RecordVariable.variable2
a! = RecordVariable.variable3
6. Close file
CLOSE #1
A Binary I/O file
OPEN "filename" FOR BINARY AS #1
The following are the only ways to input from and output to a binary file.
INPUT$
GET #1, position%, RecordVariable
GET #1, , RecordVariable ... move to the next record
PUT #1, position%+1, RecordVariable
PUT #1, , RecordVariable ... move to the next record
SEEK #1, position%
i% = SEEK(1) ... returns position of next read/write
i% = LOC(1) ... returns position of last read/write
Device I/O
COM1: input and output
CONS: output only
KYBD: input only
LPT1: output only
SCRN: output only
ex. OPEN "LPT1:" for OUTPUT AS #1
------------------------------------------------------------------------------
SHELL "filename" ... transfer control to filename and execute it
ex. INPUT "Press 1 to execute file1"; resp$
SELECT CASE resp$
CASE "1"
SHELL "file1"
:
------------------------------------------------------------------------------
SUBROUTINES & FUNCTIONS
All variables are local by default.
A function/sub can call itself (recursive)
FUNCTION name (list of variables)
statements
EXIT FUNCTION
statements
name = ... ... must have this line
END FUNCTION
... Do not use old version: DEF FN ... END DEF (which uses global variables)
(Note: FN passes variables by value not reference)
... Use function in an expression
... Make sure the name matches with the type
(Try to identify the type of the function with a suffix: $, %, etc.
ex. DECLARE FUNCTION a%
... Arguments are not mandatory.
... Do not retrive the content from the variable with the function name
because QBasic gets confused with recursive functions
ex. name = name + 1
SUB name (list of variables)
statements
EXIT SUB
statements
END SUB
... do not use old version: GOSUB ... RETURN (which uses global variables)
Two ways of calling a subroutine
CALL sub_name (list of variables)
sub_name list of variables
... no parentheses
... must declare DECLARE SUB sub_name before use in the 2nd way
so that QBasic knows that it is not a variable
argument (when apearing in CALL)
parameters (when appearing in SUB)
... fixed-length string variable cannot be a parameter appearing in SUB
... array elements cannot be a parameter appearing in SUB
... type of the variable can be declared in the parameter list
ex. SUB abc(a AS INTEGER, b%)
optional argument
FUNCTION name (list of variables, optional p) ... variable p is optional
IF IsMissing(p) Then p = 1 ' if p is missing from the argument, assign a default value
:
END FUNCTION
passing an entire array ...
DIM a(1 TO 100) AS SINGLE
CALL name(a()) ... note the use of empty parentheses
:
SUB name (b() AS SINGLE)
passing individual array elements
DIM a(1 TO 100) AS SINGLE
CALL name(a(3))
:
SUB name (b)
passing records
+TYPE newtype1
| firstname AS STRING*10
| lastname AS STRING*5
|END TYPE
|DIM b AS newtype1
| :
|CALL name (b)
+SUB name (a AS newtype2)
passing elements in records
+TYPE newtype1
| firstname AS STRING*10
| lastname AS STRING*5
|END TYPE
|DIM b AS newtype1
| :
|CALL name (b.firstname, b.lastname)
+SUB name (a$, b$)
SUB|FUNCTION name (list of variables) STATIC
... make all variables used in the subroutine static
(i.e., they retain their values between calls)
... if only a select variable need to be made static, use STATIC statements:
ex. SUB a
STATIC i%
STATIC j%() AS INTEGER + AS INTEGER must appear in both statements
DIM j%(1 TO 5) AS INTEGER +
DECLARE FUNCTION or SUB in a module (not at the procedure level, not in "Sheet1" or "ThisWorkbook")
3 cases where DECLARE must be used:
Case 1:
DECLARE FUNCTION a(x!,y!) ... must declare
:
z! = a(x!,y!)
Case 2:
DECLARE SUB a(x!,y!) ... must declare if not used as CALL
: optional if use CALL
a x!, y!
Case 3:
DECLARE SUB a(x!,y!) ... must declare if SUB a is not included in
the same module
ex. DECLARE SUB a() ... use empty parentheses if no parameters
:
CALL a
ex. DECLARE SUB a(x AS newtype)... include type of variable
$INCLUDE is usually used for:
DECLARE statements
TYPE...END TYPE definitions
COMMON statements
Do not include function/subroutine definitions in an INCLUDE file.
Usage:
' $INCLUDE: 'filename'
passing arguments by reference
Address of the variable is passed. (default)
While in subroutine, the subroutine's corresponding variable uses the same
memory location as the variable in the calling statement.
ex. i% = 1
CALL a(i%)
PRINT i% ... gives 2
:
SUB a(j%)
j% = j%+1.
END SUB
passing arguments by value
The content of the variable in the calling statement is copied into another
memory location that corresponds to the variable in the subroutine.
Expression in the argument is always passed by value.
ex. CALL a(2+3)
To pass a variable by value, enclose it in parentheses (thus, QBasic
thinks that it is an expression).
ex. CALL a( (i%) )
ex. i% = 1
CALL a( (i%) )
PRINT i% ... gives 1
CALL a( i% )
PRINT i% ... gives 2
:
SUB a(j%)
j% = j%+1
END SUB
Excel's VBA, output to cells is disallowed in a function
output to cells is disallowed in a sub with arguments
ex. FUNCTION func(x)
CELLS(1,1)=1 ... no good
END FUNCTION
ex. SUB subroutine(x)
CELLS(1,1)=1 ... no good
END SUB
-------------------------------------------------------------------------------
METACOMMANDS
Metacommands ... begin with "$" and included in comments
ex. REM $STATIC
'$INCLUDE: 'file.bi' (Note: single quotes)
-------------------------------------------------------------------------------
Files ...
QB.INI ... save changes made to the Displays Dialog Box
BC file /o; ... compile
set lib=c:\qb ... path for BCOM45.LIB or BRUN45.LIB
BCOM45.LIB ... library needed to create a stand-alone program
BRUN45.LIB ... library needed to create an abbreviated program
BRUN45.EXE ... needed by the abbreviated program at run-time
(cannot be in \dpath)
Windows
Watch window
Help window
Immediate window (holds only 10 lines)
View window
Alt key to highlight menu items.
TAB key to switch between different windows or sections in a menu.
ESC key to cancel, get out of menu, or help
F1 key to get help on any item pointed by the cursor
Undo Alt+Backspace
Cut Block Shift+Del
Copy Block Ctrl+Ins
Paste Block Shift+Ins
Delete(Clear) Block Del
SUBs F2
Next SUB Shift+F2
Output Screen F4
Find Ctrl+\
Last Find F3
Start Run Shift+F5
Run/Continue F5
Step F8
Instant Watch Shift+F9
Toggle Breakoint F9
Help F1
Help on Help Shift+F1
Last Help Level Alt+F1
Switch Window F6 or Shift+F6
Expand window Ctrl+F10
Right word Ctrl+Right
Left word Ctrl+Left
Top Window Ctrl+Home
Bottom Window Ctrl+End
Last Page PgUp
Next Page PgDn
Left Page Ctrl+PgUp
Right Page Ctrl+Pgdn
mark block Shift-direction
Del char Ctrl-BS or Shift+BS
module ... same as FORTRAN: main program
procedure ... same as FORTRAN: subroutine/function
Only one module/proprocedure can be displayed each time.
View-SUBs ... shows a list of subroutines
Return to Prof. Nam Sun Wang's Home Page
Return to Computer Methods in Chemical Engineering (CHBE250)
Computer Methods in Chemical Engineering -- QuickBasic Summary
Forward comments to:
- Nam Sun Wang
- Department of Chemical & Biomolecular Engineering
- University of Maryland
- College Park, MD 20742-2111
- 301-405-1910 (voice)
- 301-314-9126 (FAX)
-
e-mail: nsw@umd.edu
©1996-2012 by Nam Sun Wang
| |