89EB Assemble Assembly instruction/statement
Submitted by Steve Fewell
Description:
[89EB] Get the first non-space character from BASIC Text Pointer A.
Set Y and location &3D (the Mnemonic Code LSB location) to 0.
If the next character is ':', then jump to &8A5E to store current instruction (if any) and exit.
If the next character is '<cr>' [carriage return], then jump to &8A5E to store current instruction (if any) and exit.
Note: No need to check for 'ELSE', as 'ELSE' is invalid in assembly mode.
If next character is '\' then jump to &8A5E (Store current instruction (if any) and skip comment).
-
If the next characer is '.' then we need to create a label, as follows:
- * Call routine &98AE to evaluate the variable name (and create it if the variable doesn't already exist
and isn't a direct memory access.
- * If the zero flag is set on return from &98AE, then a variable was not specified, so generate 'Syntax error'.
- * If the carry flag is set on return from &98AE, then the variable was a String-variable, so generate 'Syntax
error' as an address value cannot be stored in a string variable.
- * Push variable address and type details (&2A-&2B) to the stack.
- * Set the IWA value to P% (&0440-&0441).
- * Store variable type (#&40 - Integer) in location &27.
- * Call routine &B32B to set the Numberic variable (details on Stack) to the IWA Integer value.
- * Call routine &9275 to update the BASIC Text Pointer A offset to equal the Text Pointer B offset value.
- * Store the BASIC Text Pointer A offset value in location &4E.
- * return to &89EB to skip spaces, and check for end of statement.
Decrement the BASIC Text Pointer A offset value (as the character we got last was not recognised as having a special function).
[&8A04] Encode and validate the 3-character Mnemonic value
Set X to 3 (as we will check the next 3 characters to see if they match an assembly Mnemonic Code).
[&8A06] Get next character from PTR A.
-
If the character is negative, then we have found a BASIC token, check the token for a Mnemonic code, as follows [&8A38]:
- * If token is &80 ('AND'), then set X (Mnemonic position in Mnemonic lookup table) to #&29 and jump
to &8A5E to process the assembly Mnemonic.
- * If token is &82 ('EOR'), then set X (Mnemonic position in Mnemonic lookup table) to #&2A and jump
to &8A5E to process the assembly Mnemonic.
- * If token is &84 ('OR'), then check next character. If next character is 'A' or 'a' (zeroing Bit 5 of the ASCII
value removes the upper-lower case distinction) then Set X (Mnemonic position in Mnemonic lookup table) to &2B, &
jump to &8A5E to process the assembly Mnemonic. Otherwise (next character is not 'A' or 'a') issue a 'Syntax error',
as the Assembly Mnemonic 'ORA' is not present, and we do not have a valid Assembly Mnemonic code.
- * Otherwise (as the token isn't 'AND', 'OR' or 'EOR'), the token is not a valid Assembly Mnemonic, so generate a
'Syntax error'.
If the character is a space (' '), then jump to &8A22 to check the mnemonic code found so far (as space terminates
the Mnemonic code).
Now, before we test the Mnemonic, we need to compact each character of the Mnemonic (usually 3 characters in total)
into a 2-byte code. This has 2 main advantages: (1) it saves space, and (2) it strips off the case bit from the ASCII
character, so that Mnemonics are recognised irrespective of whether they appear in upper or lower case (or a mixture
of both).
Set Y to 5 (as we will pack each character into 5-bits).
Multiply the current ASCII character by 8 (by shifting all bits left 3 places, and loosing the top 3 bits).
This leaves us with the bottom 5 bits of the ASCII code. The character has now lost its case distinction
(bit 5), so now 'A' and 'a' result in the same 5-bit value. Additionally, the #&40 (64) offset is removed,
so that 'A' is now 1, 'B' is 2, etc...
Now, move the top 5-bits of the character (the bits that are left after the earlier shift), into the bottom bit of
the 2-byte location &3D-&3E. &3D-&3E will (after all 3 Mnemonic characters have been processed in this
way) contain the 2-byte Mnemonic Code, which will uniquely identify the Assembly Mnemonic.
Decrement X (number of characters to process), and, if X is not 0, jump back to &8A06 to process the next character.
[&8A22] Check the Mnemonic code:
Now that a maximum of 3 characters have been encoded, and &3D-&3E contain 15 bits from the 3-character
Assembly Mnemonic. the coded Mnemonic (&3D-&3E) needs to be checked against the Mnemonic code lookup tables
located between address &884D and &88D6.
The Encoded Mnemonic LSB value (&3D) is looked up in the Mnemonic LSB lookup table (&884D-&8891)
(looking at the last value in the table first, then moving down towards the first value).
When a matching LSB Mnemonic value is found, the Mnemonic MSB value is then checked against the
corresponding entry in the Mnemonic MSB table (&8893-&88D6). If both codes matche then we have a valid Mnemonic
Code, so jump to &8A5E to process the Mnemonic statement.
Otherwise, continue searching with the next Mnemonic LSB code in the Mnemonic LSB table (&884D-&8891).
If the end of the Assembly Mnemonic LSB table (&884D-&8891) is reached, and the encoded Mnemonic 2-byte code
was not matched against the entries in the table, then an invalid Mnemonic was specified, so issue a 'Syntax error'.
[&8A53] A valid Assembly Mnemonic has been found! Now, start to process it
Now, X points to the position of the Assembly Mnemonic in the lookup tables.
Store the default opcode (from the Default Opcode lookup table, located at &88D7-&891B at position X) in
location &29.
Set Y = 1 (default length of Assembly Instruction is 1-byte (i.e. a single-byte Mnemonic code with no parameters)).
The Mnemonic codes in the Mnemonic lookup tables are listed in an order that enables them to be processed more easily.
I.e. the first &1F (31) Mnemonics are single-byte Instructions.
1) Check if we have a single-byte Mnemonic
If X (the Mnemonic position) is less than #&20 then we have a single-byte Mnemonic (i.e. One of the following:
BRK, CLC, CLD, CLI, CLV, DEX, DEY, INX, INY, NOP, PHA, PHP, PLA, PLP, RTI, RTS, SEC, SED, SEI, TAX, TAY, TSX, TXA, TXS,
TYA, DEA, INA, PHY, PHX, PLY, or PLX).
Single byte instructions have no parameters, and no indexing modes, so the Default Opcode (&29) is the Opcode
that we need to use, so jump to
&8A5E to store the assembly instruction.
2) Check if we have a branch-statement Mnemonic
- If X (Mnemonic position) is < #&29 then the Mnemonic is a Branch statement (i.e. one of: BCC, BCS, BEQ, BMI, BNE,
BPL, BVC, BVS or BRA), so process as follows:
- * Get the Integer result of the expression at BASIC Text pointer A (or 'Type mismatch' error if a String value was found).
- * The Integer result will be a 16-bit address value (in &2A-&2B).
- * Subtract the current physical location (P% + 1) from the address specified (by the result value).
- * (Now, Y is the LSB difference, and A is the MSB difference in the address values).
- * If Y is 0 then subtract 1 from A and decrement Y (difference is &100, treated as &FFFF (-1)).
- * If A is 0 then: * Check Y; if Y is negative (top bit set) then issue 'Out of range' error.
- * Otherwise, goto &8ADF with Y = number of Bytes to branch, as Y is within the valid range of 1 to 127.
- * If A is &FF and Y is negative, then we are branching backwards (to a previous instruction), and the branch is
- within the required ramge of -1 to -128, so goto &8ADF with Y = number of bytes to branch.
- * Otherwise, if OPT flag bit 2 is not set (errors are not reported), then skip the out of range error, and set Y
- (the number of bytes to branch) to 0 (as a placemaker, until we have the actual Branch value), and goto &8ADF.
- * [Note: OPT flag bit 2 is not set for OPT codes 0, 1, 4 & 5 (don't report errors); and it is set for 2, 3, 6
& 7 (report errors))]
- * Otherwise, if OPT flag bit 2 is set then issue an 'Out of range' error.
- * [8ADF]: Now we have a valid branch, so Store Y (bytes to branch) in &2A, set Y to 2 (length of instruction),
- and jump to &8A5E to store the assembly instruction.
3) Process Mnemonics AND, EOR, ORA, ADC, CMP, LDA, SBC (and also used by STA, see later)
If X (Mnemonic position) is < #&30 then the Mnemonic is one of the following: AND, EOR, ORA, ADC, CMP, LDA or SBC,
so process as follows:
-
* If the next non-space character is '#' then we have an immediate value indexing mode. Process as follows:
- * Add 8 to the defalt opcode (in location &29)
- * Get the Integer result of the expression at BASIC Text Pointer A (Type mismatch error if a String value was found).
- * Issue a 'Byte' error if the Integer result is more than 255 (#&FF).
- * Set Y to 2 (length of instruction is 2 bytes) and goto &8A5E to store the instruction.
- * This handles the following Mnemonic instructions:
- * AND#nn (opcode &29).
- * EOR#nn (opcode &49).
- * ORA#nn (opcode &09).
- * ADC#nn (opcode &69).
- * CMP#nn (opcode &C9).
- * LDA#nn (opcode &A9).
- * SBC#nn (opcode &E9).
- * [Note: STA does not have an immediate mode, so for STA Mnemonic, this routine is entered at &8B07].
-
* [8B07] If the next non-space character is not '(' then we have an absolute or zero page addressing mode. So:
- * [8B44] Get the Integer result of the expression at BASIC Text Pointer A (Type mismatch error if a String value was found).
- * If the next non-space character is ',' [comma] then process index-offset mode as follows:
- > Add 16 to default opcode value (&29).
- > If next character is 'Y' then add 8 to the Opcode, set Y (length of instruction) to 3, & goto &8A5E to
store the instruction.
- > -- This handles the following Mnemonic instructions:
- > AND abs,Y (opcode &39).
- > EOR abs,Y (opcode &59).
- > ORA abs,Y (opcode &19).
- > ADC abs,Y (opcode &79).
- > CMP abs,Y (opcode &D9).
- > LDA abs,Y (opcode &B9).
- > SBC abs,Y (opcode &F9).
- > STA abs,Y (opcode &99).
- > Otherwise, add 4 to the Opcode.
- > If the Integer value is a 16-bit address (more than 255) then add 8 to Opcode,
set Y to 3 (instruction is 3 bytes long) and goto &8A5E to store the instruction.
- > -- This handles the following Mnemonic instructions:
- > AND abs (opcode &2D).
- > EOR abs (opcode &4D).
- > ORA abs (opcode &0D).
- > ADC abs (opcode &6D).
- > CMP abs (opcode &CD).
- > LDA abs (opcode &AD).
- > SBC abs (opcode &ED).
- > STA abs (opcode &8D).
- > AND abs,X (opcode &3D).
- > EOR abs,X (opcode &5D).
- > ORA abs,X (opcode &1D).
- > ADC abs,X (opcode &7D).
- > CMP abs,X (opcode &DD).
- > LDA abs,X (opcode &BD).
- > SBC abs,X (opcode &FD).
- > STA abs,X (opcode &9D).
- > Otherwise, we have an 8-bit address, so set Y to 2 (length of instruction is 2 bytes),
and goto &8A5E to store the instruction.
- > -- This handles the following Mnemonic instructions:
- > AND zp (opcode &25).
- > EOR zp (opcode &45).
- > ORA zp (opcode &05).
- > ADC zp (opcode &65).
- > CMP zp (opcode &C5).
- > LDA zp (opcode &A5).
- > SBC zp (opcode &E5).
- > STA zp (opcode &85).
- > AND zp,X (opcode &35).
- > EOR zp,X (opcode &55).
- > ORA zp,X (opcode &15).
- > ADC zp,X (opcode &75).
- > CMP zp,X (opcode &D5).
- > LDA zp,X (opcode &B5).
- > SBC zp,X (opcode &F5).
- > STA zp,X (opcode &95).
-
* [8B0B] If the next non-space character is '(' then we have an indirect addressing mode. So:
- * Get the Integer result of the expression at BASIC Text Pointer A (Type mismatch error if a String value was found).
- * If the next character is ")" then we do not have an indirectly indexed instruction, so process as follows:
- > Add 16 to default opcode value (&29).
- > If next character is not ',' [comma] then Add 1 to the opcode and issue 'Byte' error
if the integer value is > 255; otherwise, set Y to 2 (length of instruction) and goto &8A5E to store the instruction.
- > -- This handles the following Mnemonic instructions:
- > AND(zp) (opcode &32).
- > EOR(zp) (opcode &52).
- > ORA(zp) (opcode &12).
- > ADC(zp) (opcode &72).
- > CMP(zp) (opcode &D2).
- > LDA(zp) (opcode &B2).
- > SBC(zp) (opcode &F2).
- > STA(zp) (opcode &92).
- > If next character is ',' [comma] then issue 'Index' error if the next non-space character
is not 'Y' or 'y', or 'Byte' error if the Integer result is > 255; otherwise,
set Y to 2 (length of instruction) and goto &8A5E to store the instruction.
- > -- This handles the following Mnemonic instructions:
- > AND(zp),Y (opcode &31).
- > EOR(zp),Y (opcode &51).
- > ORA(zp),Y (opcode &11).
- > ADC(zp),Y (opcode &71).
- > CMP(zp),Y (opcode &D1).
- > LDA(zp),Y (opcode &B1).
- > SBC(zp),Y (opcode &F1).
- > STA(zp),Y (opcode &91).
- > .
- > .
- > .
- * Otherwise (next character is not ')') issue 'Index' error if a ',' [Comma] is not the next non-space character.
- * Issue 'Index' error if the next non-space character after the ',' is not 'X' or 'x'.
- * Issue 'Index' error if the next non-space character after the 'X', or 'x', is not ')'.
- * Issue 'Byte' error if the Integer value is more than 255.
- * [Note: no opcode changes for this indexing mode, as the opcode used is the default Opcode for the Mnemonic].
- * Set Y to 2 (length of instruction is 2 bytes) and goto &8A5E to store the instruction.
- * This handles the following Mnemonic instructions:
- * AND(zp,X) (opcode &21).
- * EOR(zp,X) (opcode &41).
- * ORA(zp,X) (opcode &01).
- * ADC(zp,X) (opcode &61).
- * CMP(zp,X) (opcode &C1).
- * LDA(zp,X) (opcode &A1).
- * SBC(zp,X) (opcode &E1).
- * STA(zp,X) (opcode &81).
4) Process Mnemonic STA
If X (Mnemonic position) is < #&41 then the Mnemonic is STA. STA is handled in the same way as AND, EOR, ORA, ADC,
CMP, LDA and SBC, except that it doesn't have an immediate '#' addressing mode.
so process by jumping to
&8B07 (above), which skips the Immediate addressing mode and continues to process the
other addressing modes.
5) Process Mnemonics ASL, LSR, ROL, ROR, DEC and INC (and also used by BIT, see later)
[&8B67] If X (Mnemonic position) is < #&36 then the Mnemonic is one of the following: ASL, LSR, ROL, ROR, DEC or INC,
so process as follows:
-
* If the next non-space character is 'A' or 'a' then the Mnemonic could be an Accumulator operator, so:
- * Check the next character after the 'A' or 'a'. If the next character is not valid variable name character
('A'-'Z','a'-'z','0'-'9','_' or '£') then the A refers to the Accumulator, so:
- * If X (Mnemonic position) < #&34 (ASL, LSR, ROL or ROR) then add 4 to the opcode (&29).
- * Otherwise, if X = #&34 (DEC) then set the opcode to #&3A.
- * Otherwise, if X = #&35 (INC) then set the opcode to #&1A.
- * Set Y to 1 (length of instruction) and goto &8A5E to store the instruction.
- -- This handles the following Mnemonic instructions:
- ASL A (opcode &0A).
- LSR A (opcode &4A).
- ROL A (opcode &2A).
- ROR A (opcode &6A).
- DEC A (opcode &3A).
- INC A (opcode &1A).
- [Note: BIT does not have an accumulator mode, so for BIT Mnemonic, this routine is entered at &8B74].
- * Otherwise:
- * [&8B74] Get the Integer result of the expression at BASIC Text pointer A.
- * Get the next non-space character at BASIC Text pointer A.
- * If the next character is "," [comma] then :
- * Add 16 to the Opcode (&29).
- * If the next non-space character is not "X" or "x" then 'Index' error
- * [8B61] If 16-bit Integer then add 8 to Opcode (&29), Set Y = 3 and Store instruction.
- * Otherwise, Set Y to 2 and Store instruction.
- * This handles the following Mnemonic instructions:
- ASL abs (opcode &0E).
- LSR abs (opcode &4E).
- ROL abs (opcode &2E).
- ROR abs (opcode &6E).
- DEC abs (opcode &CE).
- INC abs (opcode &EE).
- BIT abs (opcode &2C).
- ASL abs,X (opcode &1E).
- LSR abs,X (opcode &5E).
- ROL abs,X (opcode &3E).
- ROR abs,X (opcode &7E).
- DEC abs,X (opcode &DE).
- INC abs,X (opcode &FE).
- BIT abs,X (opcode &3C).
- ASL zp (opcode &06).
- LSR zp (opcode &46).
- ROL zp (opcode &26).
- ROR zp (opcode &66).
- DEC zp (opcode &C6).
- INC zp (opcode &E6).
- BIT zp (opcode &24).
- ASL zp,X (opcode &16).
- LSR zp,X (opcode &56).
- ROL zp,X (opcode &36).
- ROR zp,X (opcode &76).
- DEC zp,X (opcode &D6).
- INC zp,X (opcode &F6).
- BIT zp,X (opcode &34).
6) Process Mnemonics CLR and STZ
If X (Mnemonic position) is < #&38 then the Mnemonic is one of the following: CLR or STZ.
Both of these Mnemonics represent the same Opcode (default Opcode value=&9C). Process as follows:
* Get the Integer result of the expression at BASIC Text pointer A (or 'Type mismatch' error if a String value was found).
* If Integer is an 8-bit address then set X to #&0F, Opcode (&29) to #&64 and Y to 2.
* If Integer is a 16-bit address then set X to #&01 and Y to 3.
* [8BB7] Store Y to the Stack.
* If the next non-space characetr is not "," then pop Y and
Store Intruction.
* If the next non-space character is not 'X' or 'x', then issue a 'Index' error.
* Otherwise, add (1 + X) to the Opcode value (&29), Pop Y from the stack (length of instruction), and
Store instruction.
* This handles the following Mnemonic instructions:
STZ (or CLR) zp (opcode &64).
STZ (or CLR) zp,X (opcode &74).
STZ (or CLR) abs (opcode &9C).
STZ (or CLR) abs,X (opcode &9E).
7) Process Mnemonics CPX, CPY, TSB or TRB
If X (Mnemonic position) is < #&3C then the Mnemonic is one of the following: CPX, CPY, TSB or TRB,
so process as follows:
* If the Mnemonic is CPX or CPY then check for Immediaate mode (TSB and TRB do not have an Immediate addressing mode):
If the next non-space character is '#' then [8BE7] Get Integer value of expression, if the Integer is greater than
255 then issue 'Byte' error, otherwise set Y to 2, and
Store Intruction.
This handles the following Mnemonic instructions:
CPX# nn (Opcode &E0)
CPY# nn (Opcode &C0)
Otherwise (if char not '#'), decrement BASIC Text Pointer A offset.
* [&8BD9] Get Integer result of expression from BASIC Text Pointer A (Convert Float value to Integer or issue 'Type mismatch'
error if a String value was found).
* [&8B5E] Add 4 to the Opcode value (&29).
* If Integer is an 8-bit value (< 256) then (zero page addressing mode) Set Y to 2 (length is 2 bytes) &
Store Instruction.
* Otherwise (Integer is an 16-bit value) (> 255), Add 8 to Opcode (&29), Set Y to 3 (length is 3 bytes) and
Store Instruction.
* This handles the following Mnemonic instructions:
CPX zp (opcode &E4).
CPY zp (opcode &C4).
TSB zp (opcode &04).
TRB zp (opcode &14).
CPX abs (opcode &EC).
CPY abs (opcode &CC).
TSB abs (opcode &0C).
TRB abs (opcode &1C).
8) Process Mnemonics BIT, JSR and JMP
If X (Mnemonic position) is < #&3F then the Mnemonic is one of the following: BIT, JSR or JMP,
so process as follows:
-
* If the Mnemonic is BIT, then:
- * [&8BDE] If the next non-space character is not '#' then goto &8B74 (in step 5 above) to process BIT in the same
way as the Absolute, Absolute,X, Zero Page and Zero Page,X addressing modes for Mnemonics ASL, LSR, ROL, ROR, DEC and INC.
- * Otherwise, we have BIT with Immediate mode addressing (which couldn't be handled by &8B74, as ASL, LSR, ROL, ROR,
DEC and INC do not have an immediate mode. Process as follows:
- * Set the Opcode (&29) to #&89 (Instruction: BIT# nn).
- * [&8BF2] Get Integer result of the expression at BASIC Text Pointer A.
- * If the Integer result is > 255 then issue 'Byte' error. Otherwise set Y to 2 and Store Instruction.
- * This handles the following Mnemonic instruction:
- BIT#nn (opcode &89).
-
* If the Mnemonic is JSR, then:
- * [&8BFB] Get Integer value of the expression at BASIC Text Pointer A.
- * Set Y to 3 (length of instruction is 3 bytes) and goto &8A5E to store the instruction.
- * This handles the following Mnemonic instruction:
- JSR abs (opcode &20).
-
* If the Mnemonic is JMP, then:
- * If the next non-space character is not '(' then Decrement BASIC Text Pointer A offset and get Integer result of
expression at Text Pointer A, Set Y to 3 and Store Instruction.
- This handles the following Mnemonic instruction:
- JMP abs (opcode &4C - the default opcode for JMP).
- * Otherwise:
- * Add 32 to the opcode (&29).
- * Get the Integer result of expression at BASIC Text pointer A ('Type mismatch' error if String found).
- * If the next non-space character is ')' then Set Y to 3 and Store Instruction.
- This handles the following Mnemonic instruction:
- JMP (abs) (opcode &6C).
- * Otherwise:
- * Issue 'Index' error if the next non-space character is not ',' [comma].
- * Add 16 to the Opcode (&29).
- * Issue 'Index' error if the next non-space character is not 'X' or 'x'.
- * Issue 'Index' error if the next non-space character is not ')'.
- * Set Y to 3 (length of instruction is 3 bytes) and goto &8A5E to store the instruction.
- * This handles the following Mnemonic instruction:
- JMP (abs,X) (opcode &7C).
9) Process Mnemonics LDX, LDY, STX or STY
If X (Mnemonic position) is < #&44 then the Mnemonic is one of the following: LDX, LDY, STX or STY,
so process as follows:
-
* Load Encoded Mnemonic LSB byte in A.
* EOR the LSB Mnemonic code with #&01 (to reverse bit 0) and AND it with #&1F (to clear the top 3 bits).
(Now A contains the last letter of the Mnemonic code (minus 64).
* Store A to the Stack.
* If the Mnemonic is LDX or LDY then:
- * (LDX and LDY have Immediate and Absolute,X (or Absolute,Y) addressing modes that STX and STY do not have).
- * [&8C38] If the next non-space character is '#' then Retrieve A from the stack (as no longer needed), Get Integer result from
expression at BASIC text pointer A, Set Y to 2, issue 'Byte' error if Integer is > 255; otherwise Store Instruction.
- This handles the following Mnemonic instructions:
- LDX#nn (opcode &A2).
- LDY#nn (opcode &A0).
- * Otherwise:
- * [&8C40] Decrement BASIC Text Pointer A offset & get the Integer result of the expression at Text Pointer A.
- * Retrieve A from the stack and store it in location &37.
- * If the next non-space character is ',' [comma] then:
- * Get the next non-space character and AND the value with #&1F (to remove
the &64 ASCII letter offset, and also removes case sensitivity).
- * Compare the result with &37 location. If equal then issue 'Index' error, as
the Index character after the comma is the same as the register operator in the Mnemonic - which is invalid.
- * Add 16 to the Opcode (&29) and continue with &8B5E, below:
- * [&8B5E] Add 4 to the opcode (&29).
- * If the Integer is > 255 (16-bit address) then add 8 to the Opcode (&29), Set Y to 3 and Store Instruction.
- * Otherwise (Integer is < 256 (8-bit zero-page address)), so set Y to 2 and Store Instruction.
- * This handles the following Mnemonic instructions:
- * LDX abs (opcode &AE).
- * LDY abs (opcode &AC).
- * LDX abs,Y (opcode &BE).
- * LDY abs,X (opcode &BC).
- * LDX zp (opcode &A6).
- * LDY zp (opcode &A4).
- * LDX zp,Y (opcode &B6).
- * LDY zp,X (opcode &B4).
-
* If the Mnemonic is STX or STY then:
- * (STX and STY do not have the Immediate and Absolute,X (or Absolute,Y) addressing modes that LDX and LDY have).
- * [&8C59] Get the Integer result of the expression at Text Pointer A.
- * Retrieve A from the stack and store it in location &37.
- * If the next non-space character is ',' [comma] then:
- * Get the next non-space character and AND the value with #&1F (to remove
the &64 ASCII letter offset (and also removes case sensitivity)).
- * Compare the result with &37 location. If equal then issue 'Index' error, as
the Index character after the comma is the same as the register operator in the Mnemonic - which is invalid.
- * Add 16 to the Opcode (&29).
- * If the Integer is > 255 then issue 'Byte' error as only zero page addressing is allowed (STX zp,Y & STY zp,X).
- * Otherwise, continue with &8B61, below:
- * [&8B61] If the Integer is > 255 (16-bit address) then add 8 to the Opcode (&29), Set Y to 3 and Store Instruction.
- * Otherwise (Integer is < 256 (8-bit zero-page address)), so set Y to 2 and Store Instruction.
- * This handles the following Mnemonic instructions:
- * STX abs (opcode &8E).
- * STY abs (opcode &8C).
- * STX zp (opcode &86).
- * STY zp (opcode &84).
- * STX zp,Y (opcode &96).
- * STY zp,X (opcode &94).
10) Process Pseudo Mnemonic OPT
If X (Mnemonic position) is = #&44 then the Mnemonic is OPT so process as follows:
* Get the Integer result of the expression at Text Pointer A.
* Store LSB of the Integer result (&2A) in &28 [OPT flag location].
* Set Y to 0 (No bytes to store) and goto
&8A5E to store the instruction (nothing!) & exit.
11) Process Pseudo Mnemonic EQU
If X (Mnemonic position) is = #&45 then the Mnemonic is EQU so process as follows:
* Increment BASIC Text Pointer A offset and get the next character after the EQU Mnemonic.
* AND the character code with #&DF to clear the case bit (bit 5), Now we have the Upper Case representation of the letter.
* If the next character is '
B' then Get Integer result of the expression at BASIC Stack pointer A, Store
IWA value in
locations &29 - &2C. Set Y to 1 (as we will store only the first byte (&2A) of the IWA value) and goto
&8A5E to store.
* If the next character is '
W' then Get Integer result of the expression at BASIC Stack pointer A, Store
IWA value in
locations &29 - &2C. Set Y to 2 (as we will store 2 bytes of the IWA value) and goto
&8A5E to store.
* If the next character is '
D' then Get Integer result of the expression at BASIC Stack pointer A, Store
IWA value in
locations &29 - &2C. Set Y to 4 (as we will store 4 bytes of the IWA value) and goto
&8A5E to store.
* If the next character is not 'S' then issue 'Syntax' error as the Instruction Line does not contain a valid Mnemonic.
* If the next character is '
S' then Store &28 (OPT flag) to the stack (for safe keeping), Get the result of the expression
at BASIC Stack pointer A, ('Type mismatch' error if not String value). Retrieve OPT Flag from the Stack. Call &9275
to set BASIC Text Pointer A Offset to BASIC Text Pointer B Offset. Set Y to #&FF (to indicate that the storage bytes
are in the
SWA) and goto
&8A5E to store.
[&8A5E] Store Assembly Instruction
Now, &29 contains the appropriate Opcode and &2A-&2B contain any parameters, and Y contains the length (number
of bytes) of the Assembly instruction.
Store Y (Length of instruction) in location &39.
Store P% LSB (&0440) in location &37.
Store P% MSB (&0441) in location &38.
X = P% MSB and A = P% LSB.
If OPT (&28) >= 4 (relocate), then X = O% MSB (&043D) and A = O% LSB (&043C).
Store A in &3A and X in &3B.
Now: &37-&38 contain the execution location (P%) and &3A-&3B contain the physical location (P%,
or O% (if OPT > 3)).
If the number of bytes (Y) is 0 then exit (RTS), as there are no instruction bytes to store.
If the number of bytes is a negative value, then the storage length is determined by the length of the
SWA,
as we are storing a String value (EQUS), so, copy the SWA value (&0600-&0600+&36) to the physical location
(&3A-&3B), and increment P% (&0400-&0441) by 1 for each byte stored.
Otherwise, copy locations &29 to (&28 + Number of Bytes (Y)) to the physical location (&3A-&3B), and
increment P% by 1 for each byte stored.
Note: Y is used as an offset pointer when copying, so no need to increment the physical location pointer, &3A-&3B.
If carry flag is set (meaning that OPT (&28) was >= 4 --> as no statements between &8A67 and &8A98
affect the carry flag), then increment O% for each byte stored.
Exit (RTS), as the assembly instruction has now been stored.
Table of Assembly instructions and Opcodes (Included here for reference)
[where: 'rel' represents a relative address (i.e. +06), 'abs' an absolute (or 16-bit) address i.e. 8005), 'zp' a zero-page
(or 8-bit) address (i.e. 56) and 'nn' a literal].
[a '*' represents an Instruction that is not in the 6502 processor, and is new for the 6502C12 (BBC Master) processor].
Opcode |
Instruction |
|
Opcode |
Instruction |
00 |
BRK |
|
80 |
BRA rel * |
01 |
ORA (zp,X) |
|
81 |
STA (zp,X) |
02 |
--- |
|
82 |
--- |
03 |
--- |
|
83 |
--- |
04 |
TSB zp * |
|
84 |
STY zp |
05 |
ORA zp |
|
85 |
STA zp |
06 |
ASL zp |
|
86 |
STX zp |
07 |
--- |
|
87 |
--- |
08 |
PHP |
|
88 |
DEY |
09 |
ORA #nn |
|
89 |
BIT #nn * |
0A |
ASL A |
|
8A |
TXA |
0B |
--- |
|
8B |
--- |
0C |
TSB abs * |
|
8C |
STY abs |
0D |
ORA abs |
|
8D |
STA abs |
0E |
ASL abs |
|
8E |
STX abs |
0F |
--- |
|
8F |
--- |
10 |
BPL rel |
|
90 |
BCC rel |
11 |
ORA (zp),Y |
|
91 |
STA (zp),Y |
12 |
ORA (zp) * |
|
92 |
STA (zp) * |
13 |
--- |
|
93 |
--- |
14 |
TRB zp * |
|
94 |
STY zp |
15 |
ORA zp,X |
|
95 |
STA zp,X |
16 |
ASL zp,X |
|
96 |
STX zp,Y |
17 |
--- |
|
97 |
--- |
18 |
CLC |
|
98 |
TYA |
19 |
ORA abs,Y |
|
99 |
STA abs,Y |
1A |
INC A * |
|
9A |
TXS |
1B |
--- |
|
9B |
--- |
1C |
TRB abs * |
|
9C |
STZ abs * |
1D |
ORA abs,X |
|
9D |
STA abs,X |
1E |
ASL abs,X |
|
9E |
STZ abs,X * |
1F |
--- |
|
9F |
--- |
20 |
JSR abs |
|
A0 |
LDY #nn |
21 |
AND (zp,X) |
|
A1 |
LDA (zp,X) |
22 |
--- |
|
A2 |
LDX #nn |
23 |
--- |
|
A3 |
--- |
24 |
BIT zp |
|
A4 |
LDY zp |
25 |
AND zp |
|
A5 |
LDA zp |
26 |
ROL zp |
|
A6 |
LDX zp |
27 |
--- |
|
A7 |
--- |
28 |
PLP |
|
A8 |
TAY |
29 |
AND #nn |
|
A9 |
LDA #nn |
2A |
ROL A |
|
AA |
TAX |
2B |
--- |
|
AB |
--- |
2C |
BIT abs |
|
AC |
LDY abs |
2D |
AND abs |
|
AD |
LDA abs |
2E |
ROL abs |
|
AE |
LDX abs |
2F |
--- |
|
AF |
--- |
30 |
BMI rel |
|
B0 |
BCS rel |
31 |
AND (zp),Y |
|
B1 |
LDA (zp),Y |
32 |
AND (zp) * |
|
B2 |
LDA (zp) * |
33 |
--- |
|
B3 |
--- |
34 |
BIT zp,X * |
|
B4 |
LDY zp |
35 |
AND zp,X |
|
B5 |
LDA zp,X |
36 |
ROL zp,X |
|
B6 |
LDX sp,Y |
37 |
--- |
|
B7 |
--- |
38 |
SEC |
|
B8 |
CLV |
39 |
AND abs,Y |
|
B9 |
LDA abs,Y |
3A |
DEC A * |
|
BA |
TSX |
3B |
--- |
|
BB |
--- |
3C |
BIT abs,X * |
|
BC |
LDY abs,X |
3D |
ORA abs,X |
|
BD |
LDA abs,X |
3E |
ASL abs,X |
|
BE |
LDX abs,Y |
3F |
--- |
|
BF |
--- |
40 |
RTI |
|
C0 |
CPY #nn |
41 |
EOR (zp,X) |
|
C1 |
CMP (zp,X) |
42 |
--- |
|
C2 |
--- |
43 |
--- |
|
C3 |
--- |
44 |
--- |
|
C4 |
CPY zp |
45 |
EOR zp |
|
C5 |
CMP zp |
46 |
LSR zp |
|
C6 |
DEC zp |
47 |
--- |
|
C7 |
--- |
48 |
PHA |
|
C8 |
INY |
49 |
EOR #nn |
|
C9 |
CMP #nn |
4A |
LSR A |
|
CA |
DEX |
4B |
--- |
|
CB |
--- |
4C |
JMP abs |
|
CC |
CPY abs |
4D |
EOR abs |
|
CD |
CMP abs |
4E |
LSR abs |
|
CE |
DEC abs |
4F |
--- |
|
CF |
--- |
50 |
BVC rel |
|
D0 |
BNE rel |
51 |
EOR (zp),Y |
|
D1 |
CMP (zp),Y |
52 |
EOR (zp) * |
|
D2 |
CMP (zp) * |
53 |
--- |
|
D3 |
--- |
54 |
--- |
|
D4 |
--- |
55 |
EOR zp,X |
|
D5 |
CMP zp,X |
56 |
LSR zp,X |
|
D6 |
DEC zp,X |
57 |
--- |
|
D7 |
--- |
58 |
CLI |
|
D8 |
CLD |
59 |
EOR abs,Y |
|
D9 |
CMP abs,Y |
5A |
PHY * |
|
DA |
PHX * |
5B |
--- |
|
DB |
--- |
5C |
--- |
|
DC |
--- |
5D |
EOR abs,X |
|
DD |
CMP abs,X |
5E |
LSR abs,X |
|
DE |
DEC abs,X |
5F |
--- |
|
DF |
--- |
60 |
RTS |
|
E0 |
CPX #nn |
61 |
ADC (zp,X) |
|
E1 |
SBC (zp,X) |
62 |
--- |
|
E2 |
--- |
63 |
--- |
|
E3 |
--- |
64 |
STZ zp * |
|
E4 |
CPX zp |
65 |
ADC zp |
|
E5 |
SBC zp |
66 |
ROR zp |
|
E6 |
INC zp |
67 |
--- |
|
E7 |
--- |
68 |
PLA |
|
E8 |
INX |
69 |
ADC #nn |
|
E9 |
SBC #nn |
6A |
ROR A |
|
EA |
NOP |
6B |
--- |
|
EB |
--- |
6C |
JMP (abs) |
|
EC |
CPX abs |
6D |
ADC abs |
|
ED |
SBC abs |
6E |
ROR abs |
|
EE |
INC abs |
6F |
--- |
|
EF |
--- |
70 |
BCS rel |
|
F0 |
BEQ rel |
71 |
ADC (zp),Y |
|
F1 |
SBC (zp),Y |
72 |
ADC (zp) * |
|
F2 |
SBC (zp) * |
73 |
--- |
|
F3 |
--- |
74 |
STZ zp,X * |
|
F4 |
--- |
75 |
ADC zp,X |
|
F5 |
SBC zp,X |
76 |
ROR zp,X |
|
F6 |
INC zp,X |
77 |
--- |
|
F7 |
--- |
78 |
SEI |
|
F8 |
SED |
79 |
ADC abs,Y |
|
F9 |
SBC abs,Y |
7A |
PLY * |
|
FA |
PLX * |
7B |
--- |
|
FB |
--- |
7C |
JMP (abs,X) * |
|
FC |
--- |
7D |
ADC abs,X |
|
FD |
SBC abs,X |
7E |
ROR abs,X |
|
FE |
INC abs,X |
7F |
--- |
|
FF |
--- |
[&884D-&891B] Assembly Mnemonic and default Opcode tables
There are 3 tables are stored at locations &884D-&8891 (Mnemonic MSB), &8892-&88D6 (Mnemonic LSB) and
&88D7-&891B (default Opcode). These tables help to decode the Assembly Mnemonics and to obtain the correct opcodes.
The values contained in these tables is as follows:
Num |
Address |
Encoded Mnemonic MSB byte |
|
Address |
Encoded Mnemonic LSB byte |
|
Address |
Default Opcode |
|
Mnemonic |
01 |
884D |
4B |
|
8892 |
0A |
|
88D7 |
00 |
|
BRK |
02 |
884E |
83 |
|
8893 |
0D |
|
88D8 |
18 |
|
CLC |
03 |
884F |
84 |
|
8894 |
0D |
|
88D9 |
D8 |
|
CLD |
04 |
8850 |
89 |
|
8895 |
0D |
|
88DA |
58 |
|
CLI |
05 |
8851 |
96 |
|
8896 |
0D |
|
88DB |
B8 |
|
CLV |
06 |
8852 |
B8 |
|
8897 |
10 |
|
88DC |
CA |
|
DEX |
07 |
8853 |
B9 |
|
8898 |
10 |
|
88DD |
88 |
|
DEY |
08 |
8854 |
D8 |
|
8899 |
25 |
|
88DE |
E8 |
|
INX |
09 |
8855 |
D9 |
|
889A |
25 |
|
88DF |
C8 |
|
INY |
0A |
8856 |
F0 |
|
889B |
39 |
|
88E0 |
EA |
|
NOP |
0B |
8857 |
01 |
|
889C |
41 |
|
88E1 |
48 |
|
PHA |
0C |
8858 |
10 |
|
889D |
41 |
|
88E2 |
08 |
|
PHP |
0D |
8859 |
81 |
|
889E |
41 |
|
88E3 |
68 |
|
PLA |
0E |
885A |
90 |
|
889F |
41 |
|
88E4 |
28 |
|
PLP |
0F |
885B |
89 |
|
88A0 |
4A |
|
88E5 |
40 |
|
RTI |
10 |
885C |
93 |
|
88A1 |
4A |
|
88E6 |
60 |
|
RTS |
11 |
885D |
A3 |
|
88A2 |
4C |
|
88E7 |
38 |
|
SEC |
12 |
885E |
A4 |
|
88A3 |
4C |
|
88E8 |
F8 |
|
SED |
13 |
885F |
A9 |
|
88A4 |
4C |
|
88E9 |
78 |
|
SEI |
14 |
8860 |
38 |
|
88A5 |
50 |
|
88EA |
AA |
|
TAX |
15 |
8861 |
39 |
|
88A6 |
50 |
|
88EB |
A8 |
|
TAY |
16 |
8862 |
78 |
|
88A7 |
52 |
|
88EC |
BA |
|
TSX |
17 |
8863 |
01 |
|
88A8 |
53 |
|
88ED |
8A |
|
TXA |
18 |
8864 |
13 |
|
88A9 |
53 |
|
88EE |
9A |
|
TXS |
19 |
8865 |
21 |
|
88AA |
53 |
|
88EF |
98 |
|
TYA |
1A |
8866 |
A1 |
|
88AB |
10 |
|
88F0 |
3A |
|
DEA [New 6502C12 Mnemonic] |
1B |
8867 |
C1 |
|
88AC |
25 |
|
88F1 |
1A |
|
INA [New 6502C12 Mnemonic] |
1C |
8868 |
19 |
|
88AD |
41 |
|
88F2 |
5A |
|
PHY [New 6502C12 Mnemonic] |
1D |
8869 |
18 |
|
88AE |
41 |
|
88F3 |
DA |
|
PHX [New 6502C12 Mnemonic] |
1E |
886A |
99 |
|
88AF |
41 |
|
88F4 |
7A |
|
PLY [New 6502C12 Mnemonic] |
1F |
886B |
98 |
|
88B0 |
41 |
|
88F5 |
FA |
|
PLX [New 6502C12 Mnemonic] [End of single-byte Mnemonics] |
20 |
886C |
63 |
|
88B1 |
08 |
|
88F6 |
90 |
|
BCC [Start of Branch Mnemonics] |
21 |
886D |
73 |
|
88B2 |
08 |
|
88F7 |
B0 |
|
BCS |
22 |
886E |
B1 |
|
88B3 |
08 |
|
88F8 |
F0 |
|
BEQ |
23 |
886F |
A9 |
|
88B4 |
09 |
|
88F9 |
30 |
|
BMI |
24 |
8870 |
C5 |
|
88B5 |
09 |
|
88FA |
D0 |
|
BNE |
25 |
8871 |
0C |
|
88B6 |
0A |
|
88FB |
10 |
|
BPL |
26 |
8872 |
C3 |
|
88B7 |
0A |
|
88FC |
50 |
|
BVC |
27 |
8873 |
D3 |
|
88B8 |
0A |
|
88FD |
70 |
|
BVS |
28 |
8874 |
41 |
|
88B9 |
0A |
|
88FE |
80 |
|
BRA [New 6502C12 Mnemonic] [End of Branch Mnemonics] |
29 |
8875 |
C4 |
|
88BA |
05 |
|
88FF |
21 |
|
AND |
2A |
8876 |
F2 |
|
88BB |
15 |
|
8900 |
41 |
|
EOR |
2B |
8877 |
41 |
|
88BC |
3E |
|
8901 |
01 |
|
ORA |
2C |
8878 |
83 |
|
88BD |
04 |
|
8902 |
61 |
|
ADC |
2D |
8879 |
B0 |
|
88BE |
0D |
|
8903 |
C1 |
|
CMP |
2E |
887A |
81 |
|
88BF |
30 |
|
8904 |
A1 |
|
LDA |
2F |
887B |
43 |
|
88C0 |
4C |
|
8905 |
E1 |
|
SBC |
30 |
887C |
6C |
|
88C1 |
06 |
|
8906 |
06 |
|
ASL |
31 |
887D |
72 |
|
88C2 |
32 |
|
8907 |
46 |
|
LSR |
32 |
887E |
EC |
|
88C3 |
49 |
|
8908 |
26 |
|
ROL |
33 |
887F |
F2 |
|
88C4 |
49 |
|
8909 |
66 |
|
ROR |
34 |
8880 |
A3 |
|
88C5 |
10 |
|
890A |
C6 |
|
DEC |
35 |
8881 |
C3 |
|
88C6 |
25 |
|
890B |
E6 |
|
INC |
36 |
8882 |
92 |
|
88C7 |
0D |
|
890C |
9C |
|
CLR |
37 |
8883 |
9A |
|
88C8 |
4E |
|
890D |
9C |
|
STZ |
38 |
8884 |
18 |
|
88C9 |
0E |
|
890E |
E0 |
|
CPX |
39 |
8885 |
19 |
|
88CA |
0E |
|
890F |
C0 |
|
CPY |
3A |
8886 |
62 |
|
88CB |
52 |
|
8910 |
00 |
|
TSB |
3B |
8887 |
42 |
|
88CC |
52 |
|
8911 |
10 |
|
TRB |
3C |
8888 |
34 |
|
88CD |
09 |
|
8912 |
24 |
|
BIT |
3D |
8889 |
B0 |
|
88CE |
29 |
|
8913 |
4C |
|
JMP |
3E |
888A |
72 |
|
88CF |
2A |
|
8914 |
20 |
|
JSR |
3F |
888B |
98 |
|
88D0 |
30 |
|
8915 |
A2 |
|
LDX |
40 |
888C |
99 |
|
88D1 |
30 |
|
8016 |
A0 |
|
LDY |
41 |
888D |
81 |
|
88D2 |
4E |
|
8917 |
81 |
|
STA |
42 |
888E |
98 |
|
88D3 |
4E |
|
8918 |
86 |
|
STX |
43 |
888F |
99 |
|
88D4 |
4E |
|
8919 |
8A |
|
STY |
44 |
8890 |
14 |
|
88D5 |
3E |
|
891A |
3A |
|
OPT |
45 |
8891 |
35 |
|
88D6 |
16 |
|
891B |
85 |
|
EQU |
Disassembly for the Assemble Assembly instruction/statement routine
89D4 |
|
032 174 152 |
20 AE 98 |
JSR &98AE Evaluate variable name & create new variable |
89D7 |
\ |
240 092 |
F0 5C |
BEQ 92 --> &8A35 [JMP &9B69 Syntax error] |
89D9 |
Z |
176 090 |
B0 5A |
BCS 90 --> &8A35 [JMP &9B69 Syntax error] |
89DB |
C |
032 067 188 |
20 43 BC |
JSR &BC43 Push &2A, &2B & &2C to the 6502 Stack |
89DE |
|
032 132 173 |
20 84 AD |
JSR &AD84 Set IWA to P% |
89E1 |
' |
133 039 |
85 27 |
STA &27 |
89E3 |
+ |
032 043 179 |
20 2B B3 |
JSR &B32B Set numeric variable |
89E6 |
u |
032 117 146 |
20 75 92 |
JSR &9275 Set PTR A Offset to PTR B Offset |
89E9 |
N |
132 078 |
84 4E |
STY &4E |
89EB |
|
032 224 142 |
20 E0 8E |
JSR &8EE0 Get next non-space char (PTR A) |
89EE |
|
160 000 |
A0 00 |
LDY#&00 |
89F0 |
d= |
100 061 |
64 3D |
STZ &3D |
89F2 |
: |
201 058 |
C9 3A |
CMP#&3A |
89F4 |
h |
240 104 |
F0 68 |
BEQ 104 --> &8A5E Store current instruction (if any) and exit |
89F6 |
|
201 013 |
C9 0D |
CMP#&0D |
89F8 |
d |
240 100 |
F0 64 |
BEQ 100 --> &8A5E Store current instruction (if any) and exit |
89FA |
\ |
201 092 |
C9 5C |
CMP#&5C |
89FC |
` |
240 096 |
F0 60 |
BEQ 96 --> &8A5E Store current instruction (if any) and exit |
89FE |
. |
201 046 |
C9 2E |
CMP#&2E |
8A00 |
|
240 210 |
F0 D2 |
BEQ -46 --> &89D4 Create label |
8A02 |
|
198 010 |
C6 0A |
DEC &0A |
8A04 |
|
162 003 |
A2 03 |
LDX#&03 |
8A06 |
|
164 010 |
A4 0A |
LDY &0A |
8A08 |
|
230 010 |
E6 0A |
INC &0A |
8A0A |
|
177 011 |
B1 0B |
LDA (&0B),Y |
8A0C |
0* |
048 042 |
30 2A |
BMI 42 --> &8A38 Check for BASIC tokens that are also Mnemonics |
8A0E |
|
201 032 |
C9 20 |
CMP#&20 |
8A10 |
|
240 016 |
F0 10 |
BEQ 16 --> &8A22 |
8A12 |
|
160 005 |
A0 05 |
LDY#&05 |
8A14 |
|
010 |
0A |
ASL A |
8A15 |
|
010 |
0A |
ASL A |
8A16 |
|
010 |
0A |
ASL A |
8A17 |
|
010 |
0A |
ASL A |
8A18 |
&= |
038 061 |
26 3D |
ROL &3D |
8A1A |
&> |
038 062 |
26 3E |
ROL &3E |
8A1C |
|
136 |
88 |
DEY |
8A1D |
|
208 248 |
D0 F8 |
BNE -8 --> &8A17 |
8A1F |
|
202 |
CA |
DEX |
8A20 |
|
208 228 |
D0 E4 |
BNE -28 --> &8A06 |
8A22 |
E |
162 069 |
A2 45 |
LDX#&45 |
8A24 |
= |
165 061 |
A5 3D |
LDA &3D |
8A26 |
L |
221 076 136 |
DD 4C 88 |
CMP &884C,X |
8A29 |
|
208 007 |
D0 07 |
BNE 7 --> &8A32 |
8A2B |
|
188 145 136 |
BC 91 88 |
LDY &8891,X |
8A2E |
> |
196 062 |
C4 3E |
CPY &3E |
8A30 |
! |
240 033 |
F0 21 |
BEQ 33 --> &8A53 |
8A32 |
|
202 |
CA |
DEX |
8A33 |
|
208 241 |
D0 F1 |
BNE -15 --> &8A26 |
8A35 |
Li |
076 105 155 |
4C 69 9B |
JMP &9B69 Syntax error |
8A38 |
) |
162 041 |
A2 29 |
LDX#&29 |
8A3A |
|
201 128 |
C9 80 |
CMP#&80 |
8A3C |
|
240 021 |
F0 15 |
BEQ 21 --> &8A53 |
8A3E |
|
232 |
E8 |
INX |
8A3F |
|
201 130 |
C9 82 |
CMP#&82 |
8A41 |
|
240 016 |
F0 10 |
BEQ 16 --> &8A53 |
8A43 |
|
232 |
E8 |
INX |
8A44 |
|
201 132 |
C9 84 |
CMP#&84 |
8A46 |
|
208 237 |
D0 ED |
BNE -19 --> &8A35 [JMP &9B69 Syntax error] |
8A48 |
|
230 010 |
E6 0A |
INC &0A |
8A4A |
|
200 |
C8 |
INY |
8A4B |
|
177 011 |
B1 0B |
LDA (&0B),Y |
8A4D |
) |
041 223 |
29 DF |
AND#&DF |
8A4F |
A |
201 065 |
C9 41 |
CMP#&41 |
8A51 |
|
208 226 |
D0 E2 |
BNE -30 --> &8A35 [JMP &9B69 Syntax error] |
8A53 |
|
189 214 136 |
BD D6 88 |
LDA &88D6,X |
8A56 |
) |
133 041 |
85 29 |
STA &29 |
8A58 |
|
160 001 |
A0 01 |
LDY#&01 |
8A5A |
|
224 032 |
E0 20 |
CPX#&20 |
8A5C |
H |
176 072 |
B0 48 |
BCS 72 --> &8AA6 |
8A5E |
@ |
173 064 004 |
AD 40 04 |
LDA &0440 |
8A61 |
7 |
133 055 |
85 37 |
STA &37 |
8A63 |
9 |
132 057 |
84 39 |
STY &39 |
8A65 |
( |
166 040 |
A6 28 |
LDX &28 |
8A67 |
|
224 004 |
E0 04 |
CPX#&04 |
8A69 |
A |
174 065 004 |
AE 41 04 |
LDX &0441 |
8A6C |
8 |
134 056 |
86 38 |
STX &38 |
8A6E |
|
144 006 |
90 06 |
BCC 6 --> &8A76 |
8A70 |
< |
173 060 004 |
AD 3C 04 |
LDA &043C |
8A73 |
= |
174 061 004 |
AE 3D 04 |
LDX &043D |
8A76 |
: |
133 058 |
85 3A |
STA &3A |
8A78 |
; |
134 059 |
86 3B |
STX &3B |
8A7A |
|
152 |
98 |
TYA |
8A7B |
( |
240 040 |
F0 28 |
BEQ 40 --> &8AA5 |
8A7D |
|
016 004 |
10 04 |
BPL 4 --> &8A83 |
8A7F |
6 |
164 054 |
A4 36 |
LDY &36 |
8A81 |
" |
240 034 |
F0 22 |
BEQ 34 --> &8AA5 |
8A83 |
|
136 |
88 |
DEY |
8A84 |
) |
185 041 000 |
B9 29 00 |
LDA &0029,Y |
8A87 |
$9 |
036 057 |
24 39 |
BIT &39 |
8A89 |
|
016 003 |
10 03 |
BPL 3 --> &8A8E |
8A8B |
|
185 000 006 |
B9 00 06 |
LDA &0600,Y |
8A8E |
: |
145 058 |
91 3A |
STA (&3A),Y |
8A90 |
@ |
238 064 004 |
EE 40 04 |
INC &0440 |
8A93 |
|
208 003 |
D0 03 |
BNE 3 --> &8A98 |
8A95 |
A |
238 065 004 |
EE 41 04 |
INC &0441 |
8A98 |
|
144 008 |
90 08 |
BCC 8 --> &8AA2 |
8A9A |
< |
238 060 004 |
EE 3C 04 |
INC &043C |
8A9D |
|
208 003 |
D0 03 |
BNE 3 --> &8AA2 |
8A9F |
= |
238 061 004 |
EE 3D 04 |
INC &043D |
8AA2 |
|
152 |
98 |
TYA |
8AA3 |
|
208 222 |
D0 DE |
BNE -34 --> &8A83 |
8AA5 |
` |
096 |
60 |
RTS |
8AA6 |
) |
224 041 |
E0 29 |
CPX#&29 |
8AA8 |
< |
176 060 |
B0 3C |
BCS 60 --> &8AE6 |
8AAA |
o |
032 111 146 |
20 6F 92 |
JSR &926F Evaluate Expression at BASIC Text pointer A convert result to integer |
8AAD |
|
024 |
18 |
CLC |
8AAE |
* |
165 042 |
A5 2A |
LDA &2A |
8AB0 |
@ |
237 064 004 |
ED 40 04 |
SBC &0440 |
8AB3 |
|
168 |
A8 |
TAY |
8AB4 |
+ |
165 043 |
A5 2B |
LDA &2B |
8AB6 |
A |
237 065 004 |
ED 41 04 |
SBC &0441 |
8AB9 |
|
192 001 |
C0 01 |
CPY#&01 |
8ABB |
|
136 |
88 |
DEY |
8ABC |
|
233 000 |
E9 00 |
SBC#&00 |
8ABE |
|
240 027 |
F0 1B |
BEQ 27 --> &8ADB |
8AC0 |
|
026 |
1A |
INC A |
8AC1 |
|
208 003 |
D0 03 |
BNE 3 --> &8AC6 |
8AC3 |
|
152 |
98 |
TYA |
8AC4 |
0 |
048 025 |
30 19 |
BMI 25 --> &8ADF |
8AC6 |
( |
165 040 |
A5 28 |
LDA &28 |
8AC8 |
) |
041 002 |
29 02 |
AND#&02 |
8ACA |
|
240 018 |
F0 12 |
BEQ 18 --> &8ADE |
8ACC |
|
|
|
... Out of range error... |
8ADB |
|
152 |
98 |
TYA |
8ADC |
0 |
048 232 |
30 E8 |
BMI -24 --> &8AC6 |
8ADE |
|
168 |
A8 |
TAY |
8ADF |
* |
132 042 |
84 2A |
STY &2A |
8AE1 |
|
160 002 |
A0 02 |
LDY#&02 |
8AE3 |
L^ |
076 094 138 |
4C 5E 8A |
JMP &8A5E Store current instruction (if any) and exit |
8AE6 |
0 |
224 048 |
E0 30 |
CPX#&30 |
8AE8 |
|
176 022 |
B0 16 |
BCS 22 --> &8B00 |
8AEA |
|
032 223 140 |
20 DF 8C |
JSR &8CDF Get next non-space char (PTR A) and compare with '#' |
8AED |
|
208 024 |
D0 18 |
BNE 24 --> &8B07 |
8AEF |
|
032 204 140 |
20 CC 8C |
JSR &8CCC Add 8 to Opcode (&29) |
8AF2 |
o |
032 111 146 |
20 6F 92 |
JSR &926F Evaluate Expression at BASIC Text pointer A convert result to integer |
8AF5 |
+ |
165 043 |
A5 2B |
LDA &2B |
8AF7 |
|
240 232 |
F0 E8 |
BEQ -24 --> &8AE1 |
8AF9 |
|
|
|
... Byte error... |
8B00 |
A |
224 065 |
E0 41 |
CPX#&41 |
8B02 |
c |
208 099 |
D0 63 |
BNE 99 --> &8B67 |
8B04 |
|
032 224 142 |
20 E0 8E |
JSR &8EE0 Get next non-space char (PTR A) |
8B07 |
( |
201 040 |
C9 28 |
CMP#&28 |
8B09 |
9 |
208 057 |
D0 39 |
BNE 57 --> &8B44 |
8B0B |
o |
032 111 146 |
20 6F 92 |
JSR &926F Evaluate Expression at BASIC Text pointer A convert result to integer |
8B0E |
|
032 224 142 |
20 E0 8E |
JSR &8EE0 Get next non-space char (PTR A) |
8B11 |
) |
201 041 |
C9 29 |
CMP#&29 |
8B13 |
|
208 023 |
D0 17 |
BNE 23 --> &8B2C |
8B15 |
|
032 201 140 |
20 C9 8C |
JSR &8CC9 Add 16 to Opcode (&29) |
8B18 |
|
032 229 140 |
20 E5 8C |
JSR &8CE5 Compare next non-space [PTR A] character with ',' |
8B1B |
|
240 004 |
F0 04 |
BEQ 4 --> &8B21 |
8B1D |
) |
230 041 |
E6 29 |
INC &29 |
8B1F |
|
128 212 |
80 D4 |
BRA -44 --> &8AF5 If IWA = 8-bit value, Y = 2 & Store assembly instruction; otherwise, Byte error |
8B21 |
|
032 224 142 |
20 E0 8E |
JSR &8EE0 Get next non-space char (PTR A) |
8B24 |
) |
041 223 |
29 DF |
AND#&DF |
8B26 |
Y |
201 089 |
C9 59 |
CMP#&59 |
8B28 |
|
240 203 |
F0 CB |
BEQ -53 --> &8AF5 If IWA = 8-bit value, Y = 2 & Store assembly instruction; otherwise, Byte error |
8B2A |
|
128 016 |
80 10 |
BRA 16 --> &8B3C Index error |
8B2C |
, |
201 044 |
C9 2C |
CMP#&2C |
8B2E |
|
208 012 |
D0 0C |
BNE 12 --> &8B3C Index error |
8B30 |
|
032 215 140 |
20 D7 8C |
JSR &8CD7 Compare next non-space [PTR A] character with 'X' or 'x' |
8B33 |
|
208 007 |
D0 07 |
BNE 7 --> &8B3C Index error |
8B35 |
|
032 224 142 |
20 E0 8E |
JSR &8EE0 Get next non-space char (PTR A) |
8B38 |
) |
201 041 |
C9 29 |
CMP#&29 |
8B3A |
|
240 185 |
F0 B9 |
BEQ -71 --> &8AF5 If IWA = 8-bit value, Y = 2 & Store assembly instruction; otherwise, Byte error |
8B3C |
|
|
|
... Index error... |
8B44 |
m |
032 109 146 |
20 6D 92 |
JSR &926D Decrement TEXT POINTER A offset & evaluate Expression [PTR A] & convert result to integer |
8B47 |
|
032 229 140 |
20 E5 8C |
JSR &8CE5 Compare next non-space [PTR A] character with ',' |
8B4A |
|
208 018 |
D0 12 |
BNE 18 --> &8B5E |
8B4C |
|
032 201 140 |
20 C9 8C |
JSR &8CC9 Add 16 to Opcode (&29) |
8B4F |
|
032 215 140 |
20 D7 8C |
JSR &8CD7 Compare next non-space [PTR A] character with 'X' or 'x' |
8B52 |
|
240 010 |
F0 0A |
BEQ 10 --> &8B5E |
8B54 |
Y |
201 089 |
C9 59 |
CMP#&59 |
8B56 |
|
208 228 |
D0 E4 |
BNE -28 --> &8B3C Index error |
8B58 |
|
032 204 140 |
20 CC 8C |
JSR &8CCC Add 8 to Opcode (&29) |
8B5B |
L |
076 254 139 |
4C FE 8B |
JMP &8BFE Set number of bytes (Y) = 3 & Store assembly instruction |
8B5E |
|
032 207 140 |
20 CF 8C |
JSR &8CCF Add 4 to Opcode (&29) |
8B61 |
+ |
165 043 |
A5 2B |
LDA &2B |
8B63 |
|
208 243 |
D0 F3 |
BNE -13 --> &8B58 |
8B65 |
|
128 144 |
80 90 |
BRA -112 --> &8AF7 If IWA = 8-bit value, Y = 2 & Store assembly instruction; otherwise, Byte error |
8B67 |
6 |
224 054 |
E0 36 |
CPX#&36 |
8B69 |
6 |
176 054 |
B0 36 |
BCS 54 --> &8BA1 |
8B6B |
|
032 224 142 |
20 E0 8E |
JSR &8EE0 Get next non-space char (PTR A) |
8B6E |
) |
041 223 |
29 DF |
AND#&DF |
8B70 |
A |
201 065 |
C9 41 |
CMP#&41 |
8B72 |
|
240 018 |
F0 12 |
BEQ 18 --> &8B86 |
8B74 |
m |
032 109 146 |
20 6D 92 |
JSR &926D Decrement TEXT POINTER A offset & evaluate Expression [PTR A] & convert result to integer |
8B77 |
|
032 229 140 |
20 E5 8C |
JSR &8CE5 Compare next non-space [PTR A] character with ',' |
8B7A |
|
208 229 |
D0 E5 |
BNE -27 --> &8B61 |
8B7C |
|
032 201 140 |
20 C9 8C |
JSR &8CC9 Add 16 to Opcode (&29) |
8B7F |
|
032 215 140 |
20 D7 8C |
JSR &8CD7 Compare next non-space [PTR A] character with 'X' or 'x' |
8B82 |
|
240 221 |
F0 DD |
BEQ -35 --> &8B61 |
8B84 |
|
128 182 |
80 B6 |
BRA -74 --> &8B3C Index error |
8B86 |
|
200 |
C8 |
INY |
8B87 |
|
177 011 |
B1 0B |
LDA (&0B),Y |
8B89 |
|
032 132 141 |
20 84 8D |
JSR &8D84 Check for Variable name character or digit (in A) |
8B8C |
|
176 230 |
B0 E6 |
BCS -26 --> &8B74 |
8B8E |
|
160 022 |
A0 16 |
LDY#&16 |
8B90 |
4 |
224 052 |
E0 34 |
CPX#&34 |
8B92 |
|
144 006 |
90 06 |
BCC 6 --> &8B9A |
8B94 |
|
208 002 |
D0 02 |
BNE 2 --> &8B98 |
8B96 |
6 |
160 054 |
A0 36 |
LDY#&36 |
8B98 |
) |
132 041 |
84 29 |
STY &29 |
8B9A |
|
032 207 140 |
20 CF 8C |
JSR &8CCF Add 4 to Opcode (&29) |
8B9D |
|
160 001 |
A0 01 |
LDY#&01 |
8B9F |
_ |
128 095 |
80 5F |
BRA 95 --> &8C00 |
8BA1 |
8 |
224 056 |
E0 38 |
CPX#&38 |
8BA3 |
% |
176 037 |
B0 25 |
BCS 37 --> &8BCA |
8BA5 |
o |
032 111 146 |
20 6F 92 |
JSR &926F Evaluate Expression at BASIC Text pointer A convert result to integer |
8BA8 |
|
160 003 |
A0 03 |
LDY#&03 |
8BAA |
|
162 001 |
A2 01 |
LDX#&01 |
8BAC |
+ |
165 043 |
A5 2B |
LDA &2B |
8BAE |
|
208 007 |
D0 07 |
BNE 7 --> &8BB7 |
8BB0 |
|
162 015 |
A2 0F |
LDX#&0F |
8BB2 |
d |
169 100 |
A9 64 |
LDA#&64 |
8BB4 |
) |
133 041 |
85 29 |
STA &29 |
8BB6 |
|
136 |
88 |
DEY |
8BB7 |
Z |
090 |
5A |
PHY |
8BB8 |
|
032 229 140 |
20 E5 8C |
JSR &8CE5 Compare next non-space [PTR A] character with ',' |
8BBB |
|
208 010 |
D0 0A |
BNE 10 --> &8BC7 |
8BBD |
|
032 215 140 |
20 D7 8C |
JSR &8CD7 Compare next non-space [PTR A] character with 'X' or 'x' |
8BC0 |
|
208 194 |
D0 C2 |
BNE -62 --> &8B84 |
8BC2 |
|
138 |
8A |
TXA |
8BC3 |
e) |
101 041 |
65 29 |
ADC &29 |
8BC5 |
) |
133 041 |
85 29 |
STA &29 |
8BC7 |
z |
122 |
7A |
PLY |
8BC8 |
6 |
128 054 |
80 36 |
BRA 54 --> &8C00 |
8BCA |
< |
224 060 |
E0 3C |
CPX#&3C |
8BCC |
|
176 028 |
B0 1C |
BCS 28 --> &8BEA |
8BCE |
: |
224 058 |
E0 3A |
CPX#&3A |
8BD0 |
|
176 007 |
B0 07 |
BCS 7 --> &8BD9 |
8BD2 |
|
032 223 140 |
20 DF 8C |
JSR &8CDF Get next non-space char (PTR A) and compare with '#' |
8BD5 |
|
240 016 |
F0 10 |
BEQ 16 --> &8BE7 |
8BD7 |
|
198 010 |
C6 0A |
DEC &0A |
8BD9 |
o |
032 111 146 |
20 6F 92 |
JSR &926F Evaluate Expression at BASIC Text pointer A convert result to integer |
8BDC |
|
128 128 |
80 80 |
BRA -128 --> &8B5E |
8BDE |
|
032 223 140 |
20 DF 8C |
JSR &8CDF Get next non-space char (PTR A) and compare with '#' |
8BE1 |
|
208 145 |
D0 91 |
BNE -111 --> &8B74 |
8BE3 |
|
160 137 |
A0 89 |
LDY#&89 |
8BE5 |
) |
132 041 |
84 29 |
STY &29 |
8BE7 |
L |
076 242 138 |
4C F2 8A |
JMP &8AF2 Get Integer value; if 8-bit value, Y = 2 & Store assembly instruction; otherwise, Byte error |
8BEA |
|
240 242 |
F0 F2 |
BEQ -14 --> &8BDE |
8BEC |
> |
224 062 |
E0 3E |
CPX#&3E |
8BEE |
|
240 011 |
F0 0B |
BEQ 11 --> &8BFB |
8BF0 |
7 |
176 055 |
B0 37 |
BCS 55 --> &8C29 |
8BF2 |
|
032 224 142 |
20 E0 8E |
JSR &8EE0 Get next non-space char (PTR A) |
8BF5 |
( |
201 040 |
C9 28 |
CMP#&28 |
8BF7 |
|
240 010 |
F0 0A |
BEQ 10 --> &8C03 |
8BF9 |
|
198 010 |
C6 0A |
DEC &0A |
8BFB |
o |
032 111 146 |
20 6F 92 |
JSR &926F Evaluate Expression at BASIC Text pointer A convert result to integer |
8BFE |
|
160 003 |
A0 03 |
LDY#&03 |
8C00 |
L^ |
076 094 138 |
4C 5E 8A |
JMP &8A5E Store current instruction (if any) and exit |
8C03 |
|
032 201 140 |
20 C9 8C |
JSR &8CC9 Add 16 to Opcode (&29) |
8C06 |
|
032 201 140 |
20 C9 8C |
JSR &8CC9 Add 16 to Opcode (&29) |
8C09 |
o |
032 111 146 |
20 6F 92 |
JSR &926F Evaluate Expression at BASIC Text pointer A convert result to integer |
8C0C |
|
032 224 142 |
20 E0 8E |
JSR &8EE0 Get next non-space char (PTR A) |
8C0F |
) |
201 041 |
C9 29 |
CMP#&29 |
8C11 |
|
240 235 |
F0 EB |
BEQ -21 --> &8BFE Set number of bytes (Y) = 3 & Store assembly instruction |
8C13 |
, |
201 044 |
C9 2C |
CMP#&2C |
8C15 |
|
208 015 |
D0 0F |
BNE 15 --> &8C26 |
8C17 |
|
032 201 140 |
20 C9 8C |
JSR &8CC9 Add 16 to Opcode (&29) |
8C1A |
|
032 215 140 |
20 D7 8C |
JSR &8CD7 Compare next non-space [PTR A] character with 'X' or 'x' |
8C1D |
|
208 007 |
D0 07 |
BNE 7 --> &8C26 |
8C1F |
|
032 224 142 |
20 E0 8E |
JSR &8EE0 Get next non-space char (PTR A) |
8C22 |
) |
201 041 |
C9 29 |
CMP#&29 |
8C24 |
|
240 216 |
F0 D8 |
BEQ -40 --> &8BFE Set number of bytes (Y) = 3 & Store assembly instruction |
8C26 |
L< |
076 060 139 |
4C 3C 8B |
JMP &8B3C Index error |
8C29 |
D |
224 068 |
E0 44 |
CPX#&44 |
8C2B |
M |
176 077 |
B0 4D |
BCS 77 --> &8C7A |
8C2D |
= |
165 061 |
A5 3D |
LDA &3D |
8C2F |
I |
073 001 |
49 01 |
EOR#&01 |
8C31 |
) |
041 031 |
29 1F |
AND#&1F |
8C33 |
H |
072 |
48 |
PHA |
8C34 |
A |
224 065 |
E0 41 |
CPX#&41 |
8C36 |
! |
176 033 |
B0 21 |
BCS 33 --> &8C59 |
8C38 |
|
032 223 140 |
20 DF 8C |
JSR &8CDF Get next non-space char (PTR A) and compare with '#' |
8C3B |
|
208 003 |
D0 03 |
BNE 3 --> &8C40 |
8C3D |
h |
104 |
68 |
PLA |
8C3E |
|
128 167 |
80 A7 |
BRA -89 --> &8BE7 |
8C40 |
m |
032 109 146 |
20 6D 92 |
JSR &926D Decrement TEXT POINTER A offset & evaluate Expression [PTR A] & convert result to integer |
8C43 |
h |
104 |
68 |
PLA |
8C44 |
7 |
133 055 |
85 37 |
STA &37 |
8C46 |
|
032 229 140 |
20 E5 8C |
JSR &8CE5 Compare next non-space [PTR A] character with ',' |
8C49 |
|
208 145 |
D0 91 |
BNE -111 --> &8BDC |
8C4B |
|
032 224 142 |
20 E0 8E |
JSR &8EE0 Get next non-space char (PTR A) |
8C4E |
) |
041 031 |
29 1F |
AND#&1F |
8C50 |
7 |
197 055 |
C5 37 |
CMP &37 |
8C52 |
|
208 210 |
D0 D2 |
BNE -46 --> &8C26 |
8C54 |
|
032 201 140 |
20 C9 8C |
JSR &8CC9 Add 16 to Opcode (&29) |
8C57 |
|
128 131 |
80 83 |
BRA -125 --> &8BDC |
8C59 |
o |
032 111 146 |
20 6F 92 |
JSR &926F Evaluate Expression at BASIC Text pointer A convert result to integer |
8C5C |
h |
104 |
68 |
PLA |
8C5D |
7 |
133 055 |
85 37 |
STA &37 |
8C5F |
|
032 229 140 |
20 E5 8C |
JSR &8CE5 Compare next non-space [PTR A] character with ',' |
8C62 |
|
208 019 |
D0 13 |
BNE 19 --> &8C77 |
8C64 |
|
032 224 142 |
20 E0 8E |
JSR &8EE0 Get next non-space char (PTR A) |
8C67 |
) |
041 031 |
29 1F |
AND#&1F |
8C69 |
7 |
197 055 |
C5 37 |
CMP &37 |
8C6B |
|
208 185 |
D0 B9 |
BNE -71 --> &8C26 |
8C6D |
|
032 201 140 |
20 C9 8C |
JSR &8CC9 Add 16 to Opcode (&29) |
8C70 |
+ |
165 043 |
A5 2B |
LDA &2B |
8C72 |
|
240 003 |
F0 03 |
BEQ 3 --> &8C77 |
8C74 |
L |
076 249 138 |
4C F9 8A |
JMP &8AF9 Byte error |
8C77 |
La |
076 097 139 |
4C 61 8B |
JMP &8B61 |
8C7A |
|
208 011 |
D0 0B |
BNE 11 --> &8C87 |
8C7C |
o |
032 111 146 |
20 6F 92 |
JSR &926F Evaluate Expression at BASIC Text pointer A convert result to integer |
8C7F |
* |
165 042 |
A5 2A |
LDA &2A |
8C81 |
( |
133 040 |
85 28 |
STA &28 |
8C83 |
|
160 000 |
A0 00 |
LDY#&00 |
8C85 |
* |
128 042 |
80 2A |
BRA 42 --> &8CB1 |
8C87 |
|
162 001 |
A2 01 |
LDX#&01 |
8C89 |
|
164 010 |
A4 0A |
LDY &0A |
8C8B |
|
230 010 |
E6 0A |
INC &0A |
8C8D |
|
177 011 |
B1 0B |
LDA (&0B),Y |
8C8F |
) |
041 223 |
29 DF |
AND#&DF |
8C91 |
B |
201 066 |
C9 42 |
CMP#&42 |
8C93 |
|
240 018 |
F0 12 |
BEQ 18 --> &8CA7 |
8C95 |
|
232 |
E8 |
INX |
8C96 |
W |
201 087 |
C9 57 |
CMP#&57 |
8C98 |
|
240 013 |
F0 0D |
BEQ 13 --> &8CA7 |
8C9A |
|
162 004 |
A2 04 |
LDX#&04 |
8C9C |
D |
201 068 |
C9 44 |
CMP#&44 |
8C9E |
|
240 007 |
F0 07 |
BEQ 7 --> &8CA7 |
8CA0 |
S |
201 083 |
C9 53 |
CMP#&53 |
8CA2 |
|
240 019 |
F0 13 |
BEQ 19 --> &8CB7 |
8CA4 |
Li |
076 105 155 |
4C 69 9B |
JMP &9B69 Syntax error |
8CA7 |
|
218 |
DA |
PHX |
8CA8 |
o |
032 111 146 |
20 6F 92 |
JSR &926F Evaluate Expression at BASIC Text pointer A convert result to integer |
8CAB |
) |
162 041 |
A2 29 |
LDX#&29 |
8CAD |
|
032 198 189 |
20 C6 BD |
JSR &BDC6 Save Integer (IWA) to zero page location |
8CB0 |
z |
122 |
7A |
PLY |
8CB1 |
L^ |
076 094 138 |
4C 5E 8A |
JMP &8A5E Store current instruction (if any) and exit |
8CB4 |
L |
076 146 144 |
4C 92 90 |
JMP &9092 Type mismatch error |
8CB7 |
( |
165 040 |
A5 28 |
LDA &28 |
8CB9 |
H |
072 |
48 |
PHA |
8CBA |
/ |
032 047 157 |
20 2F 9D |
JSR &9D2F Ptr B = Ptr A & Get result of expression |
8CBD |
|
208 245 |
D0 F5 |
BNE -11 --> &8CB4 |
8CBF |
h |
104 |
68 |
PLA |
8CC0 |
( |
133 040 |
85 28 |
STA &28 |
8CC2 |
u |
032 117 146 |
20 75 92 |
JSR &9275 Set PTR A Offset to PTR B Offset |
8CC5 |
|
160 255 |
A0 FF |
LDY#&FF |
8CC7 |
|
128 232 |
80 E8 |
BRA -24 --> &8CB1 |
8CC9 |
|
032 204 140 |
20 CC 8C |
JSR &8CCC Add 8 to Opcode (&29) |
8CCC |
|
032 207 140 |
20 CF 8C |
JSR &8CCF Add 4 to Opcode (&29) |
8CCF |
) |
165 041 |
A5 29 |
LDA &29 |
8CD1 |
|
024 |
18 |
CLC |
8CD2 |
i |
105 004 |
69 04 |
ADC#&04 |
8CD4 |
) |
133 041 |
85 29 |
STA &29 |
8CD6 |
` |
096 |
60 |
RTS |
Or