Years ago, I showed how to write an Interpreter for a dialect of Lisp. Some readers appreciated it, and some asked about an interpreter for a language that isn't just a bunch of parentheses. In 2014 I saw a celebration of the 50th anniversary of the 1964 Dartmouth BASIC interpreter, and thought that I could show how to implement such an interpreter. I never quite finished in 2014, but now it is 2017, I rediscovered this unfinished file, and completed it. For those of you unfamiliar with BASIC, here is a sample program:
program = '''
10 REM POWER TABLE
11 DATA 8, 4
15 READ N0, P0
20 PRINT "N",
25 FOR P = 2 to P0
30 PRINT "N ^" P,
35 NEXT P
40 PRINT "SUM"
45 LET S = 0
50 FOR N = 2 TO N0
55 PRINT N,
60 FOR P = 2 TO P0
65 LET S = S + N ^ P
70 PRINT N ^ P,
75 NEXT P
80 PRINT S
85 NEXT N
99 END
'''
Of course I don't have to build everything from scratch in assembly language, and I don't have to worry about every byte of storage, like Kemeny, Gates, and Woz did, so my job is much easier. The interpreter consists of three phases:
"10 READ N"
becomes ['10', 'READ', 'N']
.Stmt(num=10, typ='READ', args=['N'])
.READ
statementhas the effect of an assignment: variables['N'] = data.popleft()
.
One way to turn a line of text into a list of tokens is with the findall
method of a regular expression that defines all the legal tokens:
import re
tokenize = re.compile(r'''
\d* \.? \d+ (?: E -? \d+)? | # number
SIN|COS|TAN|ATN|EXP|ABS|LOG|SQR|RND|INT|FN[A-Z]| # functions
LET|READ|DATA|PRINT|GOTO|IF|FOR|NEXT|END | # keywords
DEF|GOSUB|RETURN|DIM|REM|TO|THEN|STEP|STOP | # keywords
[A-Z]\d? | # variable names (letter + optional digit)
".*?" | # labels (strings in double quotes)
<>|>=|<= | # multi-character relational operators
\S # any non-space single character ''',
re.VERBOSE).findall
The only complicated part is the syntax for numbers: optional digits followed by an optional decimal point, some digits, and optionally a power of 10 marked by "E"
and followed by an (optional) minus sign and some digits.
Example usage of tokenize
:
tokenize('10 READ N')
['10', 'READ', 'N']
tokenize('100 PRINT "SIN(X)^2 = ", SIN(X) ^ 2')
['100', 'PRINT', '"SIN(X)^2 = "', ',', 'SIN', '(', 'X', ')', '^', '2']
That looks good. Note that my tokens are just strings; it will be the parser's job, not the tokenizer's, to recognize that '2'
is a number and 'X'
is the name of a variable. (In some interpreters, the tokenizer makes distinctions like these.)
There's one important complication: spaces don't matter in BASIC programs, so the following should all be equivalent:
10 GOTO 99
10GOTO99
10 GO TO 99
The problem is that tokenize
gets the last one wrong:
tokenize('10 GO TO 99')
['10', 'G', 'O', 'TO', '99']
My first thought was to remove all white space from the input. That would work for this example, but it would change the token "HELLO WORLD"
to "HELLOWORLD"
, which is wrong. To remove spaces everywhere except between double quotes, I can tokenize the line and join the tokens back together. Then I can re-tokenize to get the final list of tokens; I do that in my new function below called tokenizer
.
Once I have a list of tokens, I access them through this interface:
peek()
: returns the next token in tokens
(without changing tokens
), or None
if there are no more tokens.pop()
: removes and returns the next token.pop(
string)
: removes and returns the next token if it is equal to the string; else return None
and leave tokens
unchanged.pop(
predicate)
: remove and return the next token if predicate(token) is true; else return None
, leave tokens
alone.tokens = [] # Global variable to hold a list of tokens
def tokenizer(line):
"Return a list of the tokens on this line, handling spaces properly, and upper-casing."
line = ''.join(tokenize(line)) # Remove whitespace
return tokenize(line.upper())
def peek():
"Return the first token in the global `tokens`, or None if we are at the end of the line."
return (tokens[0] if tokens else None)
def pop(constraint=None):
"""Remove and return the first token in `tokens`, or return None if token fails constraint.
constraint can be None, a literal (e.g. pop('=')), or a predicate (e.g. pop(is_varname))."""
top = peek()
if constraint is None or (top == constraint) or (callable(constraint) and constraint(top)):
return tokens.pop(0)
def remove_spaces(line):
"Remove white space from line, except space inside double quotes."
return
def lines(text):
"A list of the non-empty lines in a text."
return [line for line in text.splitlines() if line]
(Note: if I expected program lines to contain many tokens, I would use a deque
instead of a list
of tokens.)
We can test tokenizer
and the related functions:
def test_tokenizer():
global tokens
assert tokenizer('X-1') == ['X', '-', '1'] # Numbers don't have a leading minus sign, so this isn't ['X', '-1']
assert tokenizer('PRINT "HELLO WORLD"') == ['PRINT', '"HELLO WORLD"']
assert tokenizer('10 GOTO 99') == tokenizer('10GOTO99') == tokenizer('10 GO TO 99') == ['10', 'GOTO', '99']
assert (tokenizer('100 PRINT "HELLO WORLD", SIN(X) ^ 2') ==
['100', 'PRINT', '"HELLO WORLD"', ',', 'SIN', '(', 'X', ')', '^', '2'])
assert (tokenizer('100IFX1+123.4+E1-12.3E4 <> 1.2E-34*-12E34+1+"HI" THEN99') ==
['100', 'IF', 'X1', '+', '123.4', '+', 'E1', '-', '12.3E4', '<>',
'1.2E-34', '*', '-', '12E34', '+', '1', '+', '"HI"', 'THEN', '99'])
assert lines('one line') == ['one line']
assert lines(program) == [
'10 REM POWER TABLE',
'11 DATA 8, 4',
'15 READ N0, P0',
'20 PRINT "N",',
'25 FOR P = 2 to P0',
'30 PRINT "N ^" P,',
'35 NEXT P',
'40 PRINT "SUM"',
'45 LET S = 0',
'50 FOR N = 2 TO N0',
'55 PRINT N,',
'60 FOR P = 2 TO P0',
'65 LET S = S + N ^ P',
'70 PRINT N ^ P,',
'75 NEXT P',
'80 PRINT S',
'85 NEXT N',
'99 END']
assert [tokenizer(line) for line in lines(program)] == [
['10', 'REM', 'P', 'O', 'W', 'E', 'R', 'T', 'A', 'B', 'L', 'E'],
['11', 'DATA', '8', ',', '4'],
['15', 'READ', 'N0', ',', 'P0'],
['20', 'PRINT', '"N"', ','],
['25', 'FOR', 'P', '=', '2', 'TO', 'P0'],
['30', 'PRINT', '"N ^"', 'P', ','],
['35', 'NEXT', 'P'],
['40', 'PRINT', '"SUM"'],
['45', 'LET', 'S', '=', '0'],
['50', 'FOR', 'N', '=', '2', 'TO', 'N0'],
['55', 'PRINT', 'N', ','],
['60', 'FOR', 'P', '=', '2', 'TO', 'P0'],
['65', 'LET', 'S', '=', 'S', '+', 'N', '^', 'P'],
['70', 'PRINT', 'N', '^', 'P', ','],
['75', 'NEXT', 'P'],
['80', 'PRINT', 'S'],
['85', 'NEXT', 'N'],
['99', 'END']]
tokens = tokenizer('10 GO TO 99')
assert peek() == '10'
assert pop() == '10'
assert peek() == 'GOTO'
assert pop() == 'GOTO'
assert peek() == '99'
assert pop(str.isalpha) == None # '99' is not alphabetic
assert pop('98.6') == None # '99' is not '98.6'
assert peek() == '99'
assert pop(str.isnumeric) == '99' # '99' is numeric
assert peek() is None and not tokens
return 'ok'
test_tokenizer()
'ok'
lines(program)
['10 REM POWER TABLE', '11 DATA 8, 4', '15 READ N0, P0', '20 PRINT "N",', '25 FOR P = 2 to P0', '30 PRINT "N ^" P,', '35 NEXT P', '40 PRINT "SUM"', '45 LET S = 0', '50 FOR N = 2 TO N0', '55 PRINT N,', '60 FOR P = 2 TO P0', '65 LET S = S + N ^ P', '70 PRINT N ^ P,', '75 NEXT P', '80 PRINT S', '85 NEXT N', '99 END']
Parsing is the process of transforming the text of a program into an internal representation, which can then be executed. For BASIC, the representation will be an ordered list of statements, and we'll need various data types to represent the parts of the statements. I'll start by showing the grammar of BASIC statements, as seen on pages 56-57 of the manual (see also pages 26-30 for a simpler introduction). A statement starts with a line number, and then can be one of the following 15 types of statements, each type introduced by a distinct keyword:
LET
<variable>
= <expression>
READ
<list of variable>
DATA
<list of number>
PRINT
<sequence of label and expression>
GOTO
<linenumber>
IF
<expression> <relational> <expression>
THEN
<linenumber>
FOR
<varname>
= <expression>
TO
<expression> [
STEP
<expression>]
NEXT
<varname>
END
STOP
DEF
<funcname>
(<varname>
) = <expression>
GOSUB
<linenumber>
RETURN
DIM
<list of variable>
REM
<any string of characters whatsoever>
The notation <variable>
means any variable and <list of variable>
means zero or more variables, separated by commas. [
STEP
<expression>]
means that the literal string "STEP"
followed by an expression is optional.
Rather than use one of the many language parsing frameworks, I will show how to build a parser from scratch. First I'll translate the grammar above into Python. Not character-for-character (because it would take a lot of work to get Python to understand how to handle those characters), but almost word-for-word (because I can envision a straightforward way to get Python to handle the following format):
def Grammar():
return {
'LET': [variable, '=', expression],
'READ': [list_of(variable)],
'DATA': [list_of(number)],
'PRINT': [labels_and_expressions],
'GOTO': [linenumber],
'IF': [expression, relational, expression, 'THEN', linenumber],
'FOR': [varname, '=', expression, 'TO', expression, step],
'NEXT': [varname],
'END': [],
'STOP': [],
'DEF': [funcname, '(', varname, ')', '=', expression],
'GOSUB': [linenumber],
'RETURN': [],
'DIM': [list_of(variable)],
'REM': [anycharacters],
'A': []
}
The grammar of BASIC is designed so that at every point, the next token tells us unambiguously how to parse. For example, the first token after the line number defines the type of statement; also, in an expression we know that all three-letter names are functions while all 1-letter names are variables. So in writing the various grammatical category functions, a common pattern is to either peek()
at the next token or try a pop(
constraint)
, and from that decide what to parse next, and never have to back up or undo a pop()
. Here is my strategy for parsing statements:
variable
and expression
(and also statement
), will be defined as functions(with no argument) that pop tokens from the global variable tokens
, and return a data object. For example, calling linenumber()
will pop a token, convert it to an int
, and return that.
Consider parsing the statement "20 LET X = X + 1"
.
First tokenize to get: tokens = ['20', 'LET', 'X', '=', 'X', '+', '1']
.
Then call statement()
(defined below).
statement
first calls linenumber()
, getting back the integer 20
(and removing '20'
from tokens
).
Then it calls pop()
to get 'LET'
(and removing 'LET'
from tokens
).
Then it indexes into the grammar with 'LET'
, retrieving the grammar rule [variable, '=', expression]
.
Then it processes the 3 constituents of the grammar rule:
variable()
, which removes and returns 'X'
.pop('=')
, which removes '='
from tokens
, and discard it.expression()
, which returns a representation of X + 1
; let's write that as Opcall('X', '+', 1.0)
.Finally, statement
assembles the pieces and returns Stmt(num=20, typ='LET', args=['X', Opcall('X', '+', 1.0)])
.
If anything goes wrong, call fail("
error message")
, which raises an error.
Here is the definition of statement
:
def statement():
"Parse a BASIC statement from `tokens`."
num = linenumber()
typ = pop(is_stmt_type) or fail('unknown statement type')
args = []
for p in grammar[typ]: # For each part of rule, call if callable or match if literal string
if callable(p):
args.append(p())
else:
pop(p) or fail('expected ' + repr(p))
return Stmt(num, typ, args)
Some of the grammatical categories, like expression
, are complex. But many of the categories are easy one-liners:
def number(): return (-1 if pop('-') else +1) * float(pop()) # Optional minus sign
def step(): return (expression() if pop('STEP') else 1) # 1 is the default step
def linenumber(): return (int(pop()) if peek().isnumeric() else fail('missing line number'))
def relational(): return pop(is_relational) or fail('expected a relational operator')
def varname(): return pop(is_varname) or fail('expected a variable name')
def funcname(): return pop(is_funcname) or fail('expected a function name')
def anycharacters(): tokens.clear() # Ignore tokens in a REM statement
Here are the predicates that distinguish different types of tokens:
def is_stmt_type(x): return is_str(x) and x in grammar # LET, READ, ...
def is_funcname(x): return is_str(x) and len(x) == 3 and x.isalpha() # SIN, COS, FNA, FNB, ...
def is_varname(x): return is_str(x) and len(x) in (1, 2) and x[0].isalpha() # A, A1, A2, B, ...
def is_label(x): return is_str(x) and x.startswith('"') # "HELLO WORLD", ...
def is_relational(x): return is_str(x) and x in ('<', '=', '>', '<=', '<>', '>=')
def is_number(x): return is_str(x) and x and x[0] in '.0123456789' # '3', '.14', ...
def is_str(x): return isinstance(x, str)
Note that varname
means an unsubscripted variable name (a letter by itself, like X
, or followed by a digit, like X3
), and that variable
is a varname
optionally followed by index expressions in parentheses, like A(I)
or M(2*I, 3)
:
def variable():
"Parse a possibly subscripted variable e.g. 'X3' or 'A(I)' or 'M(2*I, 3)'."
V = varname()
if pop('('):
indexes = list_of(expression)()
pop(')') or fail('expected ")" to close subscript')
return Subscript(V, indexes) # E.g. 'A(I)' => Subscript('A', ['I'])
else:
return V # E.g. 'X3'
list_of
is tricky because it works at two different times. When I write list_of(number)
in the grammar, this returns an object of class list_of
. When this object is called (just as other grammatical categories like variable
are called), the effect is that it will parse a list of number
. That list can be empty (if there are no more tokens on the line), or can be a single number, or can be several numbers separated by comma tokens. I could have defined list_of
as a function that returns a function, but I thought that it would be clearer to define it as a class, so I can clearly separate what happens at the two different times: first the __init__
method determines what category to parse, and later the __call__
method does the actual parsing.
class list_of:
"list_of(category) is a callable that parses a comma-separated list of <category>"
def __init__(self, category): self.category = category
def __call__(self):
result = ([self.category()] if tokens else [])
while pop(','):
result.append(self.category())
return result
parse
, and Handling Errors¶Most of the parsing action happens inside the function statement()
, but at the very top level, parse(program)
takes a program text (that is, a string), and parses each line by calling parse_line
, sorting the resulting list of lines by line number. If we didn't have to handle errors, this would be simple:
def parse(program): return sorted(parse_line(line) for line in lines(program))
def parse_line(line): global tokens; tokens = tokenizer(line); return statement()
To handle syntactic errors, I add to parse_line
a try/except
that catches exceptions raised by calls to fail
. I acknowledge the interpreter isn't very thorough about handling all errors, and the error messages could be more helpful.
def parse_line(line):
"Return a Stmt(linenumber, statement_type, arguments)."
global tokens
tokens = tokenizer(line)
try:
stmt = statement()
if tokens: fail('extra tokens at end of line')
return stmt
except SyntaxError as err:
print("Error in line '{}' at '{}': {}".format(line, ' '.join(tokens), err))
return Stmt(0, 'REM', []) # Return dummy statement
def fail(message): raise SyntaxError(message)
A program is represented by various data structures: a list of statements, where each statement contains various components: subscripted variable references, user-defined functions, function calls, operation calls, variable names, numbers, and labels. Here I define these data structures with namedtuple
s:
from collections import namedtuple, defaultdict, deque
Stmt = namedtuple('Stmt', 'num, typ, args') # '1 GOTO 9' => Stmt(1, 'GOTO', 9)
Subscript = namedtuple('Subscript', 'var, indexes') # 'A(I)' => Subscript('A', ['I'])
Funcall = namedtuple('Funcall', 'f, x') # 'SQR(X)' => Funcall('SQR', 'X')
Opcall = namedtuple('Opcall', 'x, op, y') # 'X + 1' => Opcall('X', '+', 1)
ForState = namedtuple('ForState', 'continu, end, step') # Data for FOR loop
class Function(namedtuple('_', 'parm, body')):
"User-defined function; 'DEF FNC(X) = X ^ 3' => Function('X', Opcall('X', '^', 3))"
def __call__(self, value):
variables[self.parm] = value # Global assignment to the parameter
return evalu(self.body)
The first four namedtuples should be self-explanatory. The next one, ForState
, is used to represent the state of a FOR
loop variable while the program is running, but does not appear in the static representation of the program.
Function
is used to represent the definition of a user defined function. When the user writes "DEF FNC(X) = X ^ 3"
, we create an object with Function(parm='X', body=Opcall('X', '^', 3))
, and whenever the program calls, say, FNC(2)
in an expression, the call returns 8, and also assigns 2 to the global variable X
(whereas in modern languages, it would temporarily bind a new local variable named X
). BASIC has no local variables. Note the technique of making Function
be a subclass of a namedtuple
; we are then free to add the __call__
method to the subclass.
PRINT
Statements¶On page 26 of the manual, it appears that the grammar rule for PRINT
should be [list_of(expression)]
. But in section 3.1, More about PRINT, some complications are introduced:
","
is not a separator. A line can end with ","
.";"
can be used instead of ","
.","
or ";"
can be omitted—we can have a label immediately followed by an expression.The effect of a comma is to advance the output to the next column that is a multiple of 15 (and to a new line if this goes past column 100). The effect of a semicolon is similar, but works in multiples of 3, not 15. (Note that column numbering starts at 0, not 1.) Normally, at the end of a PRINT
statement we advance to a new line, but this is not done if the statement ends in ","
or ";"
. Here are some examples:
10 PRINT X, Y
Prints the value of X
in column 0 and Y
in column 15. Advances to new line.
20 PRINT "X =", X
Prints the string "X ="
in column 0 and the value of X
in column 15. Advances to new line.
30 PRINT "X = " X
Prints the string "X ="
in column 0 and the value of X
immediately after. Advances to new line.
40 PRINT X; Y,
Prints the value of X
in column 0, and the value of Y
in the column that is the first available multiple of 3 after that.
For example, if X
is '0'
, then print Y
in column 3, but if X
is '12345'
, then we've gone past column 3, so print Y
in column 6.
Then, because the statement ends in a comma, advance to the next column that is a multiple of 15, but not to a new line.
That explanation was long, but the implementation is short (at least for the parsing part; later we will see the execution part):
def labels_and_expressions():
"Parse a sequence of label / comma / semicolon / expression (for PRINT statement)."
result = []
while tokens:
item = pop(is_label) or pop(',') or pop(';') or expression()
result.append(item)
return result
Now for the single most complicated part of the grammar: the expression
. The biggest complication is operator precedence: the string "A + B * X + C"
should be parsed as if it were "A + (B * X) + C"
, and not as "(A + B) * (X + C),"
because multiplication binds more tightly than addition. There are many schemes for parsing expressions, I'll use an approach attributed to Keith Clarke.
Like all our grammatical categories, calling expression()
pops off some tokens and returns a data object. The first thing it does is parse one of five types of simple "primary" expressions:
a number like 1.23
;
a possibly-subscripted variable like X
or A(I)
;
a function call like SIN(X)
;
a unary negation like -X
;
or a parenthesied expression like (X + 1)
.
Next, expression
looks for infix operators. To parse 'X + 1'
as an expression, first primary()
would parse 'X'
, then it would pop off the '+'
operator, then a recursive call to expression()
would parse 1
, and the results can then be combined into an Opcall('X', '+', 1)
. If there are multiple infix operators, they can all be handled, as in 'X+1+Y+2'
, which gets parsed as Opcall(Opcall(Opcall('X', '+', 1), '+', 'Y'), '+', 2)
.
When there are multiple infix operators of different precedence, as in "A + B * X + C"
, the trick is to know which operators are parsed by the top-level call to expression
, and which by recursive calls. When we first call expression()
, the optional parameter prec
gets the default value, 1, which is the precedence of addition and subtraction. When expression
makes a recursive call, it passes the precedence of the current operator, and we only parse off operator/expression pairs at an equal or higher precedence. So, in parsing "A + B * X + C"
, when we pop off the '*'
operator (which has precedence 2), we then recursively call expression(2)
, which parses off an expression containing operators of precedence 2 or higher, which means the recursive call will parse X
, but it won't pop off the '+'
, because that is at a lower precedence. So we correctly get the structure "(A + ((B * X) + C)"
.
The function associativity
ensures that the operator '^'
is right associative, meaning 10^2^3
= (10^(2^3))
, whereas the other operators are left associative, so 10-2-3
= ((10-2)-3)
.
Here is the implementation of expression
:
def expression(prec=1):
"Parse an expression: a primary and any [op expression]* pairs with precedence(op) >= prec."
exp = primary() # 'A' => 'A'
while precedence(peek()) >= prec:
op = pop()
rhs = expression(precedence(op) + associativity(op))
exp = Opcall(exp, op, rhs) # 'A + B' => Opcall('A', '+', 'B')
return exp
def primary():
"Parse a primary expression (no infix op except maybe within parens)."
if is_number(peek()): # '1.23' => 1.23
return number()
elif is_varname(peek()): # X or A(I) or M(I+1, J)
return variable()
elif is_funcname(peek()): # SIN(X) => Funcall('SIN', 'X')
return Funcall(pop(), primary())
elif pop('-'): # '-X' => Funcall('NEG', 'X')
return Funcall('NEG', primary())
elif pop('('): # '(X)' => 'X'
exp = expression()
pop(')') or fail('expected ")" to end expression')
return exp
else:
return fail('unknown expression')
def precedence(op):
return (3 if op == '^' else 2 if op in ('*', '/', '%') else 1 if op in ('+', '-') else 0)
def associativity(op):
return (0 if op == '^' else 1)
I've now written all the grammatical categories, so I can now safely instantiate the global variable grammar
by calling Grammar()
, and parse a program:
grammar = Grammar()
parse(program)
[Stmt(num=10, typ='REM', args=[None]), Stmt(num=11, typ='DATA', args=[[8.0, 4.0]]), Stmt(num=15, typ='READ', args=[['N0', 'P0']]), Stmt(num=20, typ='PRINT', args=[['"N"', ',']]), Stmt(num=25, typ='FOR', args=['P', 2.0, 'P0', 1]), Stmt(num=30, typ='PRINT', args=[['"N ^"', 'P', ',']]), Stmt(num=35, typ='NEXT', args=['P']), Stmt(num=40, typ='PRINT', args=[['"SUM"']]), Stmt(num=45, typ='LET', args=['S', 0.0]), Stmt(num=50, typ='FOR', args=['N', 2.0, 'N0', 1]), Stmt(num=55, typ='PRINT', args=[['N', ',']]), Stmt(num=60, typ='FOR', args=['P', 2.0, 'P0', 1]), Stmt(num=65, typ='LET', args=['S', Opcall(x='S', op='+', y=Opcall(x='N', op='^', y='P'))]), Stmt(num=70, typ='PRINT', args=[[Opcall(x='N', op='^', y='P'), ',']]), Stmt(num=75, typ='NEXT', args=['P']), Stmt(num=80, typ='PRINT', args=[['S']]), Stmt(num=85, typ='NEXT', args=['N']), Stmt(num=99, typ='END', args=[])]
Here are some more tests:
def test_exp(text, repr):
"Test that text can be parsed as an expression to yield repr, with no tokens left over."
global tokens
tokens = tokenizer(text)
return (expression() == repr) and not tokens
def test_parser():
assert is_funcname('SIN') and is_funcname('FNZ') # Function names are three letters
assert not is_funcname('X') and not is_funcname('')
assert is_varname('X') and is_varname('A2') # Variables names are one letter and an optional digit
assert not is_varname('FNZ') and not is_varname('A10') and not is_varname('')
assert is_relational('>') and is_relational('>=') and not is_relational('+')
assert test_exp('A + B * X + C', Opcall(Opcall('A', '+', Opcall('B', '*', 'X')), '+', 'C'))
assert test_exp('A + B + X + C', Opcall(Opcall(Opcall('A', '+', 'B'), '+', 'X'), '+', 'C'))
assert test_exp('SIN(X)^2', Opcall(Funcall('SIN', 'X'), '^', 2))
assert test_exp('10 ^ 2 ^ 3', Opcall(10, '^', Opcall(2, '^', 3))) # right associative
assert test_exp('10 - 2 - 3', Opcall(Opcall(10, '-', 2), '-', 3)) # left associative
assert test_exp('A(I)+M(I, J)', Opcall(Subscript(var='A', indexes=['I']), '+',
Subscript(var='M', indexes=['I', 'J'])))
assert test_exp('X * -1', Opcall('X', '*', Funcall('NEG', 1.0)))
assert test_exp('X--Y--Z', Opcall(Opcall('X', '-', Funcall('NEG', 'Y')),
'-', Funcall('NEG', 'Z')))
assert test_exp('((((X))))', 'X')
return 'ok'
test_parser()
'ok'
Now that we can parse programs, we're ready to execute them. I'll first define run
to parse
and execute
a program:
def run(program): execute(parse(program))
The function execute(stmts)
first calls preprocess(stmts)
to handle declarations: DATA
and DEF
statements that are processed one time only, before the program runs, regardless of their line numbers. (DIM
statements are also declarations, but I decided that all lists/tables can have any number of elements, so I can ignore DIM
declarations.)
execute
keeps track of the state of the program, partially in three globals:
variables
: A mapping of the values of all BASIC variables (both subscripted and unsubscripted). {'P1': 3.14, ('M', (1, 1)): 42.0}
says that the value of P1
is 3.14
and M(1, 1)
is 42.0
.functions
: A mapping of the values of all BASIC functions (both built-in and user-defined). {'FNC': Function('X', Opcall('X', '^', 3)), 'SIN': math.sin}
column
: The column that PRINT
will print in next.And also with these local variables:
data
: a queue of all the numbers in DATA
statements.pc
: program counter; the index into the list of statements.ret
: the index where a RETURN
statement will return to.fors
: a map of {varname: ForState(...)}
which gives the state of each FOR
loop variable.goto
: a mapping of {linenumber: index}
, for example {10: 0, 20: 1}
for a program with two line numbers, 10 and 20.Running the program means executing the statement that the program counter (pc
) is currently pointing at, repeatedly, until we hit an END
or STOP
statement (or a READ
statement when there is no more data).
The variable pc
is initialized to 0
(the index of the first statement in the program) and is then incremented by 1
each cycle to go to the following statement; but a branching statement (GOTO
, IF
, GOSUB
, or RETURN
) can change the pc
to something other than the following statement. Note that branching statements refer to line numbers, but the pc
refers to the index number within the list of statements. The variable goto
maps from line numbers to index numbers. In BASIC there is no notion of a stack, neither for variables nor return addresses. If I do a GOSUB
to a subroutine that itself does a GOSUB
, then the original return address is lost, because BASIC has only one return address register (which we call ret
).
The main body of execute
checks the statement type, and takes appropriate action. All the statement types are straightforward, except for FOR
and NEXT
, which are explained a bit later.
def execute(stmts):
"Parse and execute the BASIC program."
global variables, functions, column
functions, data = preprocess(stmts) # {name: function,...}, deque[number,...]
variables = defaultdict(float) # mapping of {variable: value}, default 0.0
column = 0 # column to PRINT in next
pc = 0 # program counter
ret = 0 # index (pc) that a GOSUB returns to
fors = {} # runtime map of {varname: ForState(...)}
goto = {stmt.num: i # map of {linenumber: index}
for (i, stmt) in enumerate(stmts)}
while pc < len(stmts):
(_, typ, args) = stmts[pc] # Fetch and decode the instruction
pc += 1 # Increment the program counter
if typ in ('END', 'STOP') or (typ == 'READ' and not data):
return
elif typ == 'LET':
V, exp = args
let(V, evalu(exp))
elif typ == 'READ':
for V in args[0]:
let(V, data.popleft())
elif typ == 'PRINT':
basic_print(args[0])
elif typ == 'GOTO':
pc = goto[args[0]]
elif typ == 'IF':
lhs, relational, rhs, dest = args
if functions[relational](evalu(lhs), evalu(rhs)):
pc = goto[dest]
elif typ == 'FOR':
V, start, end, step = args
variables[V] = evalu(start)
fors[V] = ForState(pc, evalu(end), evalu(step))
elif typ == 'NEXT':
V = args[0]
continu, end, step = fors[V]
if ((step >= 0 and variables[V] + step <= end) or
(step < 0 and variables[V] + step >= end)):
variables[V] += step
pc = continu
elif typ == 'GOSUB':
ret = pc
pc = goto[args[0]]
elif typ == 'RETURN':
pc = ret
Here are the functions referenced by execute
:
import math
import random
import operator as op
def preprocess(stmts):
"""Go through stmts and return two values extracted from the declarations:
functions: a mapping of {name: function}, for both built-in and user-defined functions,
data: a queue of all the numbers in DATA statements."""
functions = { # A mapping of {name: function}; first the built-ins:
'SIN': math.sin, 'COS': math.cos, 'TAN': math.tan, 'ATN': math.atan,
'ABS': abs, 'EXP': math.exp, 'LOG': math.log, 'SQR': math.sqrt, 'INT': int,
'>': op.gt, '<': op.lt, '=': op.eq, '>=': op.ge, '<=': op.le, '<>': op.ne,
'^': pow, '+': op.add, '-': op.sub, '*': op.mul, '/': op.truediv, '%': op.mod,
'RND': lambda _: random.random(), 'NEG': op.neg}
data = deque() # A queue of numbers that READ can read from
for (_, typ, args) in stmts:
if typ == 'DEF':
name, parm, body = args
functions[name] = Function(parm, body)
elif typ == 'DATA':
data.extend(args[0])
return functions, data
def evalu(exp):
"Evaluate an expression, returning a number."
if isinstance(exp, Opcall):
return functions[exp.op](evalu(exp.x), evalu(exp.y))
elif isinstance(exp, Funcall):
return functions[exp.f](evalu(exp.x))
elif isinstance(exp, Subscript):
return variables[exp.var, tuple(evalu(x) for x in exp.indexes)]
elif is_varname(exp):
return variables[exp]
else: # number constant
return exp
def let(V, value):
"Assign value to the variable name or Subscripted variable."
if isinstance(V, Subscript): # A subsscripted variable
variables[V.var, tuple(evalu(x) for x in V.indexes)] = value
else: # An unsubscripted variable
variables[V] = value
FOR/NEXT
Statements¶I have to admit I don't completely understand FOR
loops. My questions include:
END
and STEP
expressions evaluated once when we first enter the FOR
loop, or each time through the loop?"FOR V = 1 TO 10"
, is the value of V
equal to 10 or 11? (Answer: the manual says 10.)"FOR V = 0 TO -2"
execute zero times? Or do all loops execute at least once, with the termination test done by the NEXT
?NEXT
statement, without ever executing the corresponding FOR
statement?NEXT
statement, without ever executing the corresponding FOR
statement, but we have previouslyexecuted a FOR
statement of a different loop that happens to use the same variable name?
I chose a solution that is easy to implement, and correctly runs all the examples in the manual, but I'm not certain that my solution is true to the original intent. Consider this program:
10 PRINT "TABLE OF SQUARES"
20 LET N = 10
30 FOR V = 1 to N STEP N/5
40 PRINT V, V * V
50 NEXT V
60 END
"FOR V"
statement in line 30, I assign:variables['V'] = 1
fors['V'] = ForState(continu=3, end=10, step=2)
where 3
is the index of line 40 (the line right after the FOR
statement); 10
is the value of N
; and 2
is the value of N/5
.
"NEXT V"
statement in line 50, I do the following:
Examine fors['V']
to check if V
incremented by the step value, 2
, is within the bounds defined by the end, 10
.
If it is, increment V
and assign pc
to be 3
, the continu
value.
If not, continue on to the following statement, 60
.
We showed how to parse a PRINT
statement with labels_and_expressions()
; now it is time to execute a PRINT
statement, printing each of the labels and expressions, and keeping track of what column to print at next, using the global variable column
.
def basic_print(items):
"Print the items (',' / ';' / label / expression) in appropriate columns."
for item in items:
if item == ',': pad(15)
elif item == ';': pad(3)
elif is_label(item): print_string(item.replace('"', ''))
else: print_string("{:g} ".format(evalu(item)))
if (not items) or items[-1] not in (',', ';'):
newline()
def print_string(s):
"Print a string, keeping track of column, and advancing to newline if at or beyond column 100."
global column
print(s, end='')
column += len(s)
if column >= 100: newline()
def pad(width):
"Pad out to the column that is the next multiple of width."
while column % width != 0:
print_string(' ')
def newline(): global column; print(); column = 0
Let's re-examine, parse, and run our first sample program:
print(program)
10 REM POWER TABLE 11 DATA 8, 4 15 READ N0, P0 20 PRINT "N", 25 FOR P = 2 to P0 30 PRINT "N ^" P, 35 NEXT P 40 PRINT "SUM" 45 LET S = 0 50 FOR N = 2 TO N0 55 PRINT N, 60 FOR P = 2 TO P0 65 LET S = S + N ^ P 70 PRINT N ^ P, 75 NEXT P 80 PRINT S 85 NEXT N 99 END
parse(program)
[Stmt(num=10, typ='REM', args=[None]), Stmt(num=11, typ='DATA', args=[[8.0, 4.0]]), Stmt(num=15, typ='READ', args=[['N0', 'P0']]), Stmt(num=20, typ='PRINT', args=[['"N"', ',']]), Stmt(num=25, typ='FOR', args=['P', 2.0, 'P0', 1]), Stmt(num=30, typ='PRINT', args=[['"N ^"', 'P', ',']]), Stmt(num=35, typ='NEXT', args=['P']), Stmt(num=40, typ='PRINT', args=[['"SUM"']]), Stmt(num=45, typ='LET', args=['S', 0.0]), Stmt(num=50, typ='FOR', args=['N', 2.0, 'N0', 1]), Stmt(num=55, typ='PRINT', args=[['N', ',']]), Stmt(num=60, typ='FOR', args=['P', 2.0, 'P0', 1]), Stmt(num=65, typ='LET', args=['S', Opcall(x='S', op='+', y=Opcall(x='N', op='^', y='P'))]), Stmt(num=70, typ='PRINT', args=[[Opcall(x='N', op='^', y='P'), ',']]), Stmt(num=75, typ='NEXT', args=['P']), Stmt(num=80, typ='PRINT', args=[['S']]), Stmt(num=85, typ='NEXT', args=['N']), Stmt(num=99, typ='END', args=[])]
run(program)
N N ^2 N ^3 N ^4 SUM 2 4 8 16 28 3 9 27 81 145 4 16 64 256 481 5 25 125 625 1256 6 36 216 1296 2804 7 49 343 2401 5597 8 64 512 4096 10269
Rather than put together a suite of unit tests for execute
, I'll run integration tests—additional whole programs. I've also added a few assertions.
# Linear equation solver (page 3 and 19 of the manual)
run('''
10 READ A1, A2, A3, A4
15 LET D = A1 * A4 - A3 * A2
20 IF D = 0 THEN 65
30 READ B1, B2
37 LET X1 = (B1*A4 - B2 * A2) / D
42 LET X2 = ( A1 * B2 - A3 * B1)/D
55 PRINT X1, X2
60 GOTO 30
65 PRINT "NO UNIQUE SOLUTION"
70 DATA 1, 2, 4
80 DATA 2, -7, 5
85 DATA 1, 3, 4, -7
90 END
''')
assert variables['D'] != 0
assert variables['X1'] == -11/3
4 -5.5 0.666667 0.166667 -3.66667 3.83333
# Find max(sin(x)) for 0 <= x <= 3 (page 25)
run('''
5 PRINT "X VALUE", "SINE", "RESOLUTION"
10 READ D
20 LET M = -1
30 FOR X = 0 TO 3 STEP D
40 IF SIN(X) <= M THEN 80
50 LET X0 = X
60 LET M = SIN(X)
80 NEXT X
85 PRINT X0, M, D
90 GO TO 10
95 DATA .1, .01, .001, .0001
99 END
''')
assert abs(variables['X0'] - math.pi / 2) < 0.00001
X VALUE SINE RESOLUTION 1.6 0.999574 0.1 1.57 1 0.01 1.571 1 0.001 1.5708 1 0.0001
# Printing (page 32)
run('''
10 FOR I = 1 TO 12
20 PRINT I,
30 NEXT I
40 END''')
assert variables['I'] == 12
1 2 3 4 5 6 7 8 9 10 11 12
# Powers (page 33)
run('''
5 PRINT "THIS PROGRAM COMPUTES AND PRINTS THE NTH POWERS"
6 PRINT "OF THE NUMBERS LESS THAN OR EQUAL TO N FOR VARIOUS"
7 PRINT "N FROM 1 TO 7"
8 PRINT
10 FOR N = 1 TO 7
15 PRINT "N = "; N; "I^N:"
20 FOR I = 1 TO N
30 PRINT I^N,
40 NEXT I
50 PRINT
60 PRINT
70 NEXT N
80 END''')
assert variables['N'] ** variables['I'] == 7 ** 7
THIS PROGRAM COMPUTES AND PRINTS THE NTH POWERS OF THE NUMBERS LESS THAN OR EQUAL TO N FOR VARIOUS N FROM 1 TO 7 N = 1 I^N: 1 N = 2 I^N: 1 4 N = 3 I^N: 1 8 27 N = 4 I^N: 1 16 81 256 N = 5 I^N: 1 32 243 1024 3125 N = 6 I^N: 1 64 729 4096 15625 46656 N = 7 I^N: 1 128 2187 16384 78125 279936 823543
# Cubes (page 35; but with STEP -2 because I haven't tested negative step yet)
run('''
10 FOR I = 100 TO 0 STEP -2
20 PRINT I*I*I;
30 NEXT I
40 END
''')
assert variables['I'] == 0
1e+06 941192 884736 830584 778688 729000 681472 636056 592704 551368 512000 474552 438976 405224 373248 343000 314432 287496 262144 238328 216000 195112 175616 157464 140608 125000 110592 97336 85184 74088 64000 54872 46656 39304 32768 27000 21952 17576 13824 10648 8000 5832 4096 2744 1728 1000 512 216 64 8 0
# Sales ledger (page 37; cleaned up a bit)
run('''
10 FOR I = 1 TO 3
20 READ P(I)
30 NEXT I
40 FOR I = 1 TO 3
50 FOR J = 1 TO 5
60 READ S(I, J)
70 NEXT J
80 NEXT I
90 FOR J = 1 TO 5
100 LET S = 0
110 FOR I = 1 TO 3
120 LET S = S + P(I) * S(I, J)
130 NEXT I
140 PRINT "TOTAL SALES FOR SALESMAN"J, "$"S
150 NEXT J
190 DIM S(3, 5)
200 DATA 1.25, 4.30, 2.50
210 DATA 40, 20, 37, 29, 42
220 DATA 10, 16, 3, 21, 8
230 DATA 35, 47, 29, 16, 33
300 END
''')
TOTAL SALES FOR SALESMAN1 $180.5 TOTAL SALES FOR SALESMAN2 $211.3 TOTAL SALES FOR SALESMAN3 $131.65 TOTAL SALES FOR SALESMAN4 $166.55 TOTAL SALES FOR SALESMAN5 $169.4
We can look at the variables that have been stored for this program:
variables
defaultdict(float, {'J': 5.0, ('S', (3.0, 1.0)): 35.0, ('S', (3.0, 4.0)): 16.0, ('S', (3.0, 5.0)): 33.0, ('S', (1.0, 2.0)): 20.0, ('S', (1.0, 3.0)): 37.0, ('S', (2.0, 3.0)): 3.0, ('S', (2.0, 2.0)): 16.0, ('S', (1.0, 5.0)): 42.0, ('P', (1.0,)): 1.25, ('S', (3.0, 3.0)): 29.0, ('S', (2.0, 4.0)): 21.0, 'S': 169.4, 'I': 3.0, ('P', (2.0,)): 4.3, ('S', (3.0, 2.0)): 47.0, ('S', (1.0, 1.0)): 40.0, ('S', (1.0, 4.0)): 29.0, ('S', (2.0, 5.0)): 8.0, ('P', (3.0,)): 2.5, ('S', (2.0, 1.0)): 10.0})
# Random number generator (page 40)
run('''
10 FOR I = 1 TO 100
20 PRINT INT(10 * RND(X));
30 NEXT I
40 END
''')
1 2 4 9 5 0 5 3 7 7 3 8 6 4 4 6 7 4 5 4 8 8 7 9 4 1 0 3 5 2 3 4 5 3 6 5 3 1 0 9 5 6 1 4 5 7 3 1 4 3 6 3 7 2 3 0 2 2 7 5 0 8 7 9 3 9 5 7 5 0 1 9 6 3 7 5 0 0 5 7 3 5 9 3 2 6 1 2 1 9 1 7 0 9 0 6 9 6 7 2
# DEF example: table of SIN(X) and COS(X) in degrees (page 41, expanded some)
run('''
5 PRINT "D"; "SIN(D)", "COS(D)", "SIN(D)^2 + COS(D)^2"
20 LET P = 3.1415926535897932 / 180
30 FOR X = 0 TO 90 STEP 15
40 PRINT X; FNS(X), FNC(X), FNS(X)^2 + FNC(X)^2
50 NEXT X
97 DEF FNS(D) = SIN(D * P)
98 DEF FNC(D) = COS(D * P)
99 END
''')
D SIN(D) COS(D) SIN(D)^2 + COS(D)^2 0 0 1 1 15 0.258819 0.965926 1 30 0.5 0.866025 1 45 0.707107 0.707107 1 60 0.866025 0.5 1 75 0.965926 0.258819 1 90 1 6.12323e-17 1
# GOSUB (page 43)
run('''
100 LET X = 3
110 GOSUB 400
120 PRINT U, V, W
200 LET X = 5
210 GOSUB 400
215 PRINT U, V, W
220 LET Z = U + 2*V + 3*W
230 PRINT "Z = " Z
240 STOP
400 LET U = X*X
410 LET V = X*X*X
420 LET W = X*X*X*X + X*X*X + X*X + X
430 RETURN
440 END
''')
9 27 120 25 125 780 Z = 2615
# Sum of non-negative multiples of 0.1 less than or equal to 2, two ways (page 47)
run('''
5 LET S = 0
10 LET N = 0
20 LET S = S + N/10
30 IF N >= 20 THEN 60
40 LET N = N + 1
50 GOTO 20
60 PRINT S
70 END
''')
21
run('''
20 FOR N = 1 TO 20
40 LET S = S + N/10
50 NEXT N
60 PRINT S
70 END
''')
assert variables['S'] == sum(N/10 for N in range(1, 21))
21
Here we show a collection of syntax errors, and the messages they generate:
run('''
1 X = 1
2 GO TO JAIL
3 FOR I = 1
4 IF X > 0 & X < 10 GOTO 999
5 LET Z = (Z + 1
6 PRINT "OH CANADA", EH?
7 LET Z = +3
8 LET X = Y ** 2
9 LET A(I = 1
10 IF A = 0 THEN 900 + 99
11 NEXT A(I)
12 DEF F(X) = X ^ 2 + 1
13 IF X != 0 THEN 999
14 DEF FNS(X + 2*P1) = SIN(X)
15 DEF FNY(M, B) = M * X + B
16 LET 3 = X
17 LET SIN = 7 * DEADLY
18 LET X = A-1(I)
19 FOR SCORE + 7
20 STOP IN NAME(LOVE)
80 REMARKABLY, THE INTERPRETER
81 REMEDIES THE ERRORS, AND THE PROPGRAM
82 REMAINS AN EXECUTABLE ENTITY, UN-
83 REMITTENTLY RUNNING, WITH NO
84 REMORSE OR REGRETS, AND WITH GREAT
85 ENDURANCE.
98 PRINT "ADD 2 + 2 = " 2 + 2
99 END
''')
Error in line '1 X = 1' at 'X = 1': unknown statement type Error in line '2 GO TO JAIL' at 'J A I L': missing line number Error in line '3 FOR I = 1 ' at '': expected 'TO' Error in line '4 IF X > 0 & X < 10 GOTO 999' at '& X < 10 GOTO 999': expected 'THEN' Error in line '5 LET Z = (Z + 1' at '': expected ")" to end expression Error in line '6 PRINT "OH CANADA", EH?' at '?': unknown expression Error in line '7 LET Z = +3' at '+ 3': unknown expression Error in line '8 LET X = Y ** 2' at '* 2': unknown expression Error in line '9 LET A(I = 1' at '= 1': expected ")" to close subscript Error in line '10 IF A = 0 THEN 900 + 99' at '+ 99': extra tokens at end of line Error in line '11 NEXT A(I)' at '( I )': extra tokens at end of line Error in line '12 DEF F(X) = X ^ 2 + 1' at 'F ( X ) = X ^ 2 + 1': expected a function name Error in line '13 IF X != 0 THEN 999' at '! = 0 THEN 999': expected a relational operator Error in line '14 DEF FNS(X + 2*P1) = SIN(X)' at '+ 2 * P1 ) = SIN ( X )': expected ')' Error in line '15 DEF FNY(M, B) = M * X + B' at ', B ) = M * X + B': expected ')' Error in line '16 LET 3 = X' at '3 = X': expected a variable name Error in line '17 LET SIN = 7 * DEADLY' at 'SIN = 7 * D E A D L Y': expected a variable name Error in line '18 LET X = A-1(I)' at '( I )': extra tokens at end of line Error in line '19 FOR SCORE + 7' at 'C O R E + 7': expected '=' Error in line '20 STOP IN NAME(LOVE)' at 'I N N A M E ( L O V E )': extra tokens at end of line Error in line '85 ENDURANCE.' at 'U R A N C E .': extra tokens at end of line ADD 2 + 2 = 4
run('''
100 REM CONWAY'S GAME OF LIFE
102 REM G IS NUMBER OF GENERATIONS,
104 REM M IS MATRIX SIZE (M X M)
106 REM L(SELF, NEIGHBORS_ALIVE) IS 1 IFF CELL WITH THOSE COUNTS LIVES
108 REM A(X, Y) IS 1 IFF CELL AT (X, Y) IS LIVE
110 REM B(X, Y) GETS THE NEXT GENERATION
120 READ G, M, L(0,3), L(1,3), L(1,2)
121 DATA 10, 10, 1, 1, 1
130 READ A(3,4), A(3,5), A(3,6), A(6,5), A(6,6), A(7,5), A(7,6)
131 DATA 1, 1, 1, 1, 1, 1, 1
150 REM MAIN LOOP: PRINT, THEN REPEAT G TIMES: UPDATE / COPY / PRINT
155 LET I = 0
160 GOSUB 700
170 FOR I = 1 TO G
180 GOSUB 300
190 GOSUB 500
200 GOSUB 700
210 NEXT I
220 STOP
300 REM ========== UPDATE B = NEXT_GEN(A)
310 FOR Y = 1 TO M
320 FOR X = 1 TO M
325 LET N = A(X-1,Y)+A(X+1,Y)+A(X,Y-1)+A(X,Y+1)+A(X-1,Y-1)+A(X+1,Y+1)+A(X-1,Y+1)+A(X+1,Y-1)
330 LET B(X, Y) = L(A(X, Y), N)
340 NEXT X
350 NEXT Y
360 RETURN
500 REM ========== COPY A = B
510 FOR Y = 1 TO M
520 FOR X = 1 TO M
530 LET A(X, Y) = B(X, Y)
540 NEXT X
550 NEXT Y
560 RETURN
700 REM ========== PRINT A
705 PRINT "GEN " I
710 FOR Y = 1 TO M
720 FOR X = 1 TO M
730 IF A(X, Y) = 1 THEN 760
740 PRINT ".";
750 GOTO 770
760 PRINT "O";
770 NEXT X
780 PRINT
790 NEXT Y
795 RETURN
999 END
''')
GEN 0 . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . O . . . . . . . . . O . . O O . . . . . O . . O O . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . GEN 1 . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . O O O . O O . . . . . . . . O O . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . GEN 2 . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . O . . . . . . . . . O . O O O . . . . . O . O O O . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . GEN 3 . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . O . O . . . . . O O . O . O . . . . . . . O . O . . . . . . . . O . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . GEN 4 . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . O O O O . . . . . . O . O . O . . . . . . O O . O . . . . . . . . O . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . GEN 5 . . . . . . . . . . . . . . . . . . . . . . . O O . . . . . . . O . O O . . . . . . O . . . O . . . . . . O O . O . . . . . . . O O . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . GEN 6 . . . . . . . . . . . . . . . . . . . . . . . O O O . . . . . . O . O O . . . . . . O . . . O . . . . . . O O . O . . . . . . O O O . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . GEN 7 . . . . . . . . . . . . . . O . . . . . . . . O . O . . . . . . O . . . O . . . . . O . . . O . . . . . O . . . O . . . . . . O . O . . . . . . . . O . . . . . . . . . . . . . . . . . . . . . . . . . GEN 8 . . . . . . . . . . . . . . O . . . . . . . . O O O . . . . . . O O . O O . . . . O O O . O O O . . . . O O . O O . . . . . . O O O . . . . . . . . O . . . . . . . . . . . . . . . . . . . . . . . . . GEN 9 . . . . . . . . . . . . . O O O . . . . . . O . . . O . . . . O . . . . . O . . . O . . . . . O . . . O . . . . . O . . . . O . . . O . . . . . . O O O . . . . . . . . . . . . . . . . . . . . . . . . GEN 10 . . . . O . . . . . . . . O O O . . . . . . O O O O O . . . . O O . . . O O . . O O O . . . O O O . . O O . . . O O . . . . O O O O O . . . . . . O O O . . . . . . . . O . . . . . . . . . . . . . . .
Actually, this was an assignment in my high school BASIC class. (We used a slightly different version of BASIC.) Back then, output was on rolls of paper, and I thought it was wasteful to print only one generation per line. So I arranged to print multiple generations on the same line, storing them until it was time to print them out. But BASIC doesn't have three-dimensional arrays, so I needed to store several generations worth of data in one A(X, Y)
value. Today, I know that that could be done by allocating one bit for each generation, but back then I don't think I knew about binary representation, so I stored one generation in each decimal digit. That means I no longer need two matrixes, A
and B
; instead, the current generation will always be the value in the one's place, the previous generation in the ten's place, and the one before that in the hundred's place. (Also, I admit I cheated: I added the mod operatoir, %
, which did not appear in early versions of BASIC, just because it was useful for this program.)
run('''
100 REM CONWAY'S GAME OF LIFE
102 REM G IS NUMBER OF GENERATIONS,
104 REM M IS MATRIX SIZE (M X M)
106 REM L(SELF, NEIGHBORS_ALIVE) IS 1 IFF CELL WITH THOSE COUNTS LIVES
108 REM A(X, Y) STORES THE HISTORY OF THE CELL AT (X, Y); 1 MEANS LIVE,
110 REM BUT WE STORE SEVERAL GENERATIONS: A(X, Y) = 100 MEANS THE CELL
112 REM IS DEAD IN THE CURRENT AND PREVIOUS GENERATION (00), BUT LIVE IN THE
114 REM GENERATION BEFORE THAT (1). WE STORE MULTIPLE GENERATIONS SO THAT
116 REM WE CAN PRINT THEM OUT ON ONE LINE, SAVING SPACE/PAPER.
120 READ G, M, L(0,3), L(1,3), L(1,2)
122 DATA 11, 10, 1, 1, 1
124 READ A(3,4), A(3,5), A(3,6), A(6,5), A(6,6), A(7,5), A(7,6)
126 DATA 1, 1, 1, 1, 1, 1, 1
130 REM FNA(N) = THE PREVIOUS GENERATION'S VALUE
132 DEF FNA(N) = INT(N / 10) % 10
134 REM FNC(N) = THE GENERATION IN COLUMN C; FNC(123) = C FOR EACH C IN 1..3
136 DEF FNC(N) = FNA(N / (10 ^ (2 - C)))
150 REM MAIN LOOP: DO 3 UPDATES (2 FIRST TIME), THEN PRINT AND SHIFT
160 FOR I = 1 TO G
170 GOSUB 300
175 IF I % 3 <> 2 THEN 200
180 GOSUB 700
190 GOSUB 800
200 NEXT I
210 STOP
300 REM ========== UPDATE A: SHIFT OLD GENS LEFT; ADD IN NEW GEN
310 FOR Y = 1 TO M
320 FOR X = 1 TO M
330 LET A(X, Y) = 10 * A(X, Y)
340 NEXT X
350 NEXT Y
360 FOR Y = 1 TO M
370 FOR X = 1 TO M
380 LET N1 = FNA(A(X+1,Y-1)) + FNA(A(X+1,Y)) + FNA(A(X+1,Y+1)) + FNA(A(X,Y-1))
390 LET N2 = FNA(A(X-1,Y-1)) + FNA(A(X-1,Y)) + FNA(A(X-1,Y+1)) + FNA(A(X,Y+1))
400 LET S = FNA(A(X, Y))
410 LET A(X, Y) = A(X, Y) + L(S, N1 + N2)
420 NEXT X
430 NEXT Y
440 RETURN
700 REM ========== PRINT A (3 GENERATIONS ACROSS THE PAGE)
705 PRINT "GEN " I-2, " ", " GEN " I-1, " ", " GEN " I
710 FOR Y = 1 TO M
715 FOR C = 1 TO 3
720 FOR X = 1 TO M
730 IF FNC(A(X, Y)) = 1 THEN 760
740 PRINT ".";
750 GOTO 770
760 PRINT "O";
770 NEXT X
772 IF C = 3 THEN 777
775 PRINT "|";
777 NEXT C
780 PRINT
790 NEXT Y
795 RETURN
800 REM ========== FORGET ALL BUT THE MOST RECENT GENERATION IN A
810 FOR Y = 1 TO M
820 FOR X = 1 TO M
830 LET A(X, Y) = A(X, Y) % 10
840 NEXT X
850 NEXT Y
860 RETURN
999 END
''')
GEN 0 GEN 1 GEN 2 . . . . . . . . . . | . . . . . . . . . . | . . . . . . . . . . . . . . . . . . . . | . . . . . . . . . . | . . . . . . . . . . . . . . . . . . . . | . . . . . . . . . . | . . . . . . . . . . . . O . . . . . . . | . . . . . . . . . . | . . O . . . . . . . . . O . . O O . . . | . O O O . O O . . . | . . O . O O O . . . . . O . . O O . . . | . . . . . O O . . . | . . O . O O O . . . . . . . . . . . . . | . . . . . . . . . . | . . . . . . . . . . . . . . . . . . . . | . . . . . . . . . . | . . . . . . . . . . . . . . . . . . . . | . . . . . . . . . . | . . . . . . . . . . . . . . . . . . . . | . . . . . . . . . . | . . . . . . . . . . GEN 3 GEN 4 GEN 5 . . . . . . . . . . | . . . . . . . . . . | . . . . . . . . . . . . . . . . . . . . | . . . . . . . . . . | . . . . . . . . . . . . . . . . . . . . | . . . . . . . . . . | . . . O O . . . . . . . . O . O . . . . | . . O O O O . . . . | . . O . O O . . . . . O O . O . O . . . | . . O . O . O . . . | . . O . . . O . . . . . . . O . O . . . | . . . O O . O . . . | . . . O O . O . . . . . . . . O . . . . | . . . . . O . . . . | . . . . O O . . . . . . . . . . . . . . | . . . . . . . . . . | . . . . . . . . . . . . . . . . . . . . | . . . . . . . . . . | . . . . . . . . . . . . . . . . . . . . | . . . . . . . . . . | . . . . . . . . . . GEN 6 GEN 7 GEN 8 . . . . . . . . . . | . . . . . . . . . . | . . . . . . . . . . . . . . . . . . . . | . . . . O . . . . . | . . . . O . . . . . . . . O O O . . . . | . . . O . O . . . . | . . . O O O . . . . . . O . O O . . . . | . . O . . . O . . . | . . O O . O O . . . . . O . . . O . . . | . . O . . . O . . . | . O O O . O O O . . . . . O O . O . . . | . . O . . . O . . . | . . O O . O O . . . . . . O O O . . . . | . . . O . O . . . . | . . . O O O . . . . . . . . . . . . . . | . . . . O . . . . . | . . . . O . . . . . . . . . . . . . . . | . . . . . . . . . . | . . . . . . . . . . . . . . . . . . . . | . . . . . . . . . . | . . . . . . . . . . GEN 9 GEN 10 GEN 11 . . . . . . . . . . | . . . . O . . . . . | . . . O O O . . . . . . . O O O . . . . | . . . O O O . . . . | . . O . . . O . . . . . O . . . O . . . | . . O O O O O . . . | . O . . . . . O . . . O . . . . . O . . | . O O . . . O O . . | O . . . O . . . O . . O . . . . . O . . | O O O . . . O O O . | O . . O . O . . O . . O . . . . . O . . | . O O . . . O O . . | O . . . O . . . O . . . O . . . O . . . | . . O O O O O . . . | . O . . . . . O . . . . . O O O . . . . | . . . O O O . . . . | . . O . . . O . . . . . . . . . . . . . | . . . . O . . . . . | . . . O O O . . . . . . . . . . . . . . | . . . . . . . . . . | . . . . . . . . . .