A Proposed Assembly Language Syntax For 65c816 Assemblers by Randall Hyde This is a proposed standard for 65c816 assembly language. The proposed standard comes in three levels: subset, full, and extended. The subset standard is intended for simple (or inexpensive) products, particularly those aimed at beginning 65c816 assembly language programmers. The full standard is the focus of this proposal. An assembler meeting the full level adopts all of the requirements outlined in this paper. The extended level is a mechanism whereby a vendor can claim full compliance with the standard and point out that there are extensions as well. An assembler cannot claim extended level compliance unless it also complies with the full standard. An assembler, no matter how many extensions are incorporated, will have to claim subset level unless the full standard is supported. This ensures that programmers who do not use any assembler extensions can assemble their programs on any assembler meeting the full or extended compliance levels. In addition to the items required for compliance, this proposal suggests several extensions in the interests of compatibility with existing 65c816 assemblers. These recommendations are not required for full compliance with the standard, they're included in this proposal as suggestions to help make conversion of existing programs easier. The suggestions are presented in two levels: recommended and optional. Recommended items should be present in any decent 65c816 package. Inclusion of the optional items is discouraged (since there are other ways to accomplish the same operation within the confines of the standard) but may be included in the assembler at the vendor's discretion to help alleviate conversion problems. 65c816 Instruction Mnemonics ---------------------------- All of the following mnemonics are required at the subset, full, and extended standard levels. The following mnemonics handle the basic 65c816 instruction set: ADC - add with carry AND - logical AND BCC - branch if carry clear BCS - branch if carry set BEQ - branch if equal BIT - bit test BMI - branch if minus BNE - branch if not equal BPL - branch if plus BRA - branch always BRK - break point instruction BVC - branch if overflow clear BVS - branch if overflow set CLC - clear the carry flag CLD - clear the decimal flag CLI - clear the interrupt flag CLP - clear bits in P CLR - store a zero into memory CMP - compare accumulator CPX - compare x register CPY - compare y register CSP - call system procedure DEC - decrement acc or memory DEX - decrement x register DEY - decrement y register EOR - exclusive-or accumulator HLT - halt (stop) the clock INC - increment acc or memory INX - increment x register INY - increment y register JMP - jump to new location JSR - jump to subroutine LDA - load accumulator LDX - load x register LDY - load y register MVN - block move (decrement) MVP - block move (increment) NOP - no operation ORA - logical or accumulator PHA - push accumulator PHP - push p PHX - push x register PHY - push y register PLA - pop accumulator PLP - pop p PLX - pop x register PLY - pop y register PSH - push operand PUL - pop operand RET - return from subroutine ROL - rotate left acc/mem ROR - rotate right acc/mem RTI - return from interrupt RTL - return from long subroutine RTS - return from short subroutine SBC - subtract with carry SED - set decimal flag SEI - set interrupt flag SEP - set bits in P SHL - shift left acc/mem SHR - shift right acc/mem STA - store accumulator STX - store x register STY - store y register SWA - swap accumulator halves TAD - transfer acc to D TAS - transfer acc to S TAX - transfer acc to x TAY - transfer acc to y TCB - test and clear bit TDA - transfer D to acc TSA - transfer S to acc TSB - test and set bit TSX - transfer S to X TXA - transfer x to acc TXS - transfer x to S TXY - transfer x to y TYA - transfer y to acc TYX - transfer y to x WAI - wait for interrupt XCE - exchange carry with emulation bit Comments: CLP replaces REP in the original 65c816 instruction set, since CLP is a tad more consistent with the original 6502 instruction set. See "recommended options" for the status of REP. CLR replaces the STZ instruction. Since STA, STX, and STY are used to store 65c816 registers, STZ seems to imply that there is a Z register. Using CLR (clear) eliminates any confusion. CSP (call system procedure) replaces the COP mnemonic. COP was little more than a software interrupt in both intent and implementation. CSP helps make this usage a little clearer. HLT replaces the STP mnemonic. STP, like the STZ mnemonic, implies that the P register is being stored somewhere. HLT (for halt) is just as obvious as "stop the clock" yet it doesn't have the same "look and feel" as a store instruction. JML and JSL are not really required by the new standard; but see recommended options concerning these two instructions. Most of the new 65c816 push and pull instructions have been collapsed into two instructions: PSH and PUL. PEA label becomes PSH #label PEI (label) becomes PSH label PER label becomes PSH @label PHB becomes PSH DBR PHD becomes PSH D PHK becomes PSH PBR PLB becomes PUL DBR PLD becomes PUL D These mnemonics are more in line with the original design of the 6502 instruction set whereby the mnemonic specifies the operation and the operand specifies the addressing mode and address. The RET instruction gets converted to RTS or RTL, depending on the type of subroutine being declared. RTS and RTL still exist in order to force a short or long return. SHL and SHR (shift left and shift right) are used instead of ASL and LSR. The 6500 family has NEVER supported an arithmetic shift left instruction. The operation performed by the ASL mnemonic is really a logical shift left. To simplify matters, SHL and SHR are used to specify shift left and shift right. SWA (swap accumulator halves) is used instead of XBA. Since this is the only instruction that references the "B" accumulator, there's no valid reason for even treating the accumulator as two distinct entities (this is just a carry-over from the 6800 MPU). Likewise, since the eight-bit accumulator cannot be distinguished from the 16-bit accumulator on an instruction by instruction basis (it depends on the setting of the M bit in the P register), the accumulator should always be referred to as A, regardless of whether the CPU is in the eight or sixteen bit mode. Therefore, instructions like TCD, TCS, TDC, and TSC should be replaced by TAD, TAS, TDA, and TSA. For more info on these new mnemonics, see the section on "recommended options". Built-in Macros --------------- The following instructions actually generate one or more instructions. They are not required at the subset level, but are required at the full and extended levels. ADD - emits CLC then ADC BFL - emits BEQ (branch if false) BGE - emits BCS BLT - emits BCC BTR - emits BNE (branch if true) BSR - emits PER *+2 then BRA (short) or PER *+3 then BRL (long) SUB - emits SEC then SBC Recommended Options ------------------- The following mnemonics are aliases of existing instructions. The (proposed) standard recommends that the assembler support these mnemonics, mainly to provide compatibility with older source code, but does not recommend their use in new programs. Some (or all) of these items may be removed from the recommended list in future revisions of the standard. None of these recommended items need be present at the subset level. If these are the only extensions over and above the full syntax, the assembler CANNOT claim to be an extended level assembler. ASL BRL COP JML JSL LSR PEA PEI PER PHB PHK PHK PLB PLD REP TCD TCS TDC TSC TRB WDM XBA Symbols, Constants, and Other Items ----------------------------------- Symbols may contain any reasonable number of characters at the full level. At the subset compliance level, at least 16 characters should be supported and 32 is recommeded. A "reasonable" number of characters should be at least 64 if the implementor needs a maximum value. Symbols must begin with an alphabetic character and may contain (only) the following symbols: A-Z, a-z, 0-9, "_", "$", and "!". The assembler must be capable of treating upper and lower case alphabetic characters identically. Note that this does not disallow an assembler from allowing the programmer to choose that upper and lower case be distinct, it simply requires that in the default case, upper and lower case characters are treated identically. Note that the standard does not require case sensitivity in the assembler (and, in fact, recommends against it). Therefore, anyone foolish enough (for many, many reasons) to create variables that differ only in the case of the letters they contain is risking port- ability problems (as well as maintenence, readability, and other problems). The following symbols are reserved and may not be redefined within the program: A, X, Y, S, DBR, PBR, D, M, P Nor may these symbol appear as fields to a record or type definition (which will be described later). Constants take six different forms: character constants, string constants, binary constants, decimal constants, hexadecimal constants and set constants. Character constants are created by surrounding a single character by a pair of apostrophes or quotation marks, e.g., "s", "a", '$', and 'p'. If the character is surrounded by apostrophes, then the ASCII code for that character WITH THE H.O. BIT CLEAR will be used. If the quotation marks are used, then the ASCII code for the character WITH THE H.O. BIT SET will be used. If you need to represent the apostrophe with the H.O. bit clear or a quotation mark with the H.O. bit set, simply double up the characters, e.g., '''' - emits a single apostrophe. """" - emits a single quotation mark. String constants are generated by placing a sequence of two or more characters within a pair of apostrophes or quotation marks. The choice of apostrophe or quotation mark controls the H.O. bit, as for character constants. Likewise, to place an apostrophe or quote within a string delimited by the same character, just double up the apostrophe or quotation mark: 'This isn''t bad!' - generates --This isn't bad-- "He said ""Hello""" - generates --He said "Hello"-- Binary integer constants consist of a sequence of 1 through 32 zeros or ones preceded by a percent sign ("%"). Examples: %10110010 %001011101 %10 %1100 Decimal integer constants consist of strings of decimal digits without any preceding characters. E.g., 25, 235, 8325, etc. Decimal constants may be (optionally) preceded by a minus sign. Hexadecimal constants consist of a dollar sign ("$") followed by a string of hexadecimal digits (0..9 and A..F). Values in the range $0 through $FFFFFFFF are allowed. Set constants are only required at the full and extended compliance levels. A set constant consists of a list of items surrounded by braces, e.g., {0,3,5}. For more information, see the .SET directive. Address Expressions ------------------- Most instructions and many pseudo-opcode/assembler directives require operands of some sort. Often these operands contain some sort of address expression (some, ultimately, numeric or string value). This proposed standard defines the operands, precision, accuracy, and available operations that constitutes an address expression. Precision: all integer expressions are computed using 32 bits. All string expressions are computed with strings up to 255 characters in length. All floating point operations are performed using IEEE 80-bit extended floating point values (i.e., Apple SANE routines). All set operations are performed using 32 bits of precision. Accuracy: all integer operations (consisting of two 32-bit operands and an operator on those operands) must produce the correct result if the actual result can fit within 32 bits. If an overflow occurs, the value is truncated and only the low order 32 bits are retained. If an underflow occurs, zero is used as the result. If an overflow or underflow occurs, a special bit will be set (until the next value is computed) that can be tested by the ".IFOVR" and ".IFUNDR" directives. Other than that, such errors are ignored. All arithmetic is performed using unsigned arithmetic operations. All floating point operations follow the IEEE (and Apple SANE) suggestions, and are otherwise ignored by the assembler. Any string operation producing a string longer than 255 characters produces an assembly time error. All set operations must be exact. Integer operations: The following integer operations must be provided at all compliance levels: + (binary) adds the two operands. - (binary) subracts second operand from the first. * multiplies the two operands. / divides the first operand by the second. \ divides the first operand by the second and returns the remainder. & logically ANDs the two operands. | logically ORs the two operands. ^ logically XORs the two operands. = <> These operators compare the two operands (unsigned comparison) and < return 1 if the comparison is true, 0 otherwise. > <= >= - (unary) negates (2's complement) the operand ~ (unary) complements (inverts - 1's complement) the operand The following operators must be provided at the full and extended compliance levels: <- shifts the first operand to the left the number of bits specified by the second operand. -> shifts the first operand to the right the number of bits specified by the second operand. @ (unary) subtracts the location counter at the beginning of the current statement from the following address expression. % (ternary, e.g.: X%Y:Z) This operator extracts bits Y through Z from X and returns that result right justified. Floating point operations: floating point numbers and operations are required only at the full and extended levels. The following operations must be available as well: + adds the two operands. - subtracts the second operand from the first. * multiplies the two operands. / divides the first operand by the second. - (unary) negates the operand. = <> These operators compare the two operands and < return 1 if the comparison is true, 0 otherwise. > <= >= String operations: strings and string operations are not required at the subset level, but the standard recommends their presence. The following string operations must be provided at the full and extended levels: + concatenates two strings % (ternary, e.g., X%Y:Z) returns the substring composed of the characters in X starting at position Y of length Z. Generate an error if X doesn't contain sufficient characters. = <> These operators compare the two operands and < return 1 if the comparison is true, 0 otherwise. > <= >= Set operations: sets and set operations are required only at the full and extended levels. The following set operations must be provided: + union of two sets (logical OR of the bits). * intersection of two sets (logical AND of the bits). - set difference (set one ANDed with the NOT of the second set) = returns 1 if the two sets are equal, zero otherwise. <> returns 1 if the two sets are not equal, zero otherwise. < returns 1 if the first set is a proper subset of the second. <= returns 1 if the first set is a subset of the second. > returns 1 if the first set is a proper superset of the second. >= returns 1 if the first set is a superset of the second. % (ternary, e.g., X % Y:Z) extracts elements Y..Z from X and returns those items. In addition to the above operators, several pre-defined functions are also available. Note that these functions are not required at the subset compliance level, only at the full and extended levels: float(i) - Converts integer "i" to a floating point value. trunc(r) - Converts real "r" to a 32-bit unsigned integer (or generates an error). valid(r) - returns "1" if r is a valid floating point value, 0 otherwise (for example, if r is NaN, infinity, etc.) length(s)- returns the length of string s. lookup(s)- returns "1" if s is a valid symbol in the symbol table. value(s) - returns value of symbol specified by string "s" in the symbol table. type(s) - returns type of symbol "s" in symbol table. Actual values returned are yet to be defined. mode(a) - returns the addressing mode of item "a". Used mainly in macros. STR(s) - returns string s with a prefixed length byte. ZRO(s) - returns string s with a suffixed zero byte. DCI(s) - returns string s with the H.O. bit of its last char inverted. RVS(s) - returns string s with its characters reversed. FLP(s) - returns string s with its H.O. bits inverted. IN(v,s) - returns one if value v is in set s, zero otherwise. The following integer functions must be present at all compliance levels: LB(i), LBYTE(i), BYTE(i) - returns the L.O. byte of i. HB(i), HBYTE(i) - returns byte #1 (bits 8-15) of i. BB(i), BBYTE(i) - returns bank byte (bits 16-23) of i. XB, XBYTE(i) - returns H.O. byte of i. LW(i), LWORD(i), WORD(i) - returns L.O. word of i. HW(i), HWORD(i) - returns H.O. word of i. WORD(i) Pack(i,j)- returns a 16-bit value whose L.O. byte is the L.O. byte of i and whose H.O. byte is the L.O. byte of j. Pack(i,j,k,l)- returns a 32-bit value consisting of (i,j,k,l) where i is the L.O. byte and l is the H.O. byte. Note: l is optional. If it isn't present, substitute zero for l. The order of evaluation for an expression is strictly left to right unless parentheses are used to modify the precedence of a sub-expression. Since parentheses are used to specify certain indirect addressing modes, the use of paretheses to override the strict left-to-right evaluation order introduces some ambiguity. For example, should the following be treated as jump indirect through location $1001 or jump directly to location $1001? JMP ($1000+1) The ambiguity is resolved as follows: if the parenthesis is the first char- acter in the operand field, then the indirect addressing mode is assumed. Otherwise, the parentheses are used to override the left-to-right precedence. The example above would be treated as a jump indirect through location $1001. If you wanted to jump directly to location $1001 in this fashion, the state- ment could be modified to JMP 0+($1000+1) so that the parenthesis is no longer the first character in the operand field. The use of parentheses to override the left-to-right precedence is only required at the full and extended compliance levels. It is not required at the subset compliance level. Expression Types ---------------- Expressions, in addition to having a value associated with them, also have a specific type. The three basic types of expressions are integer, floating point, and string expressions. Integer expressions can be broken down into subtypes as well. A hierarchical diagram is the easiest way to describe integer expressions: integers ------ constants ------------ user defined (enumerated) types | | | +----- simple numeric constants | | +-- addresses ------------ direct page addresses | +----- absolute addresses --- full 16-bit | | | +- relative 8-bit | +----- long addresses This diagram points out that there are two types of integer expres- sions: constants and addresses. Further, there are two types of constants and four types of addresses. Before discussion operations on these different types of integer values, their purpose should be presented. Until now, most 65xxx assembler did little to differentiate between the different types of integer values. In this proposed standard, however, strong type checking is enforced. Whereas in previous assemblers you could use the following code: label equ $1000 lda #Label sta Label such operations are illegal within the confines of the new standard. The problem with this short code segment is that the symbol "label" is used as both an integer constant (in the LDA instruction) and as an address expression (in the STA instruction). To help prevent logical errors from creeping into a program, the assembler doesn't allow the use of addresses where constants are expected and vice versa. To that end, a new assembler directive, CON, is used to declare constants while EQU is used to declare an (absolute) address. Symbols declared by CON cannot be (directly) used as an address. Likewise, symbols declared by EQU (and others) cannot be used where a constant is expected (such as in an immediate operand). Although this type checking can be quite useful for locating bugs within the source file, it can also be a source of major annoyance. Some- times (quite often, in fact) you may want to treat an address expression as a constant or a constant expression as an address. Two functions are used to coerce these expressions to their desired form: PTR and OFS. PTR(expr) converts the supplied constant expression to an address expression. OFS(expr) converts the supplied address expression to a constant expression. The following is perfectly legal: Cons1 CON $5A DataLoc EQU $1000 lda #OFS(DataLoc) sta PTR(Cons1) For more information, see the section on assembler directives. PTR and OFS are required at all compliance levels of this proposed standard. While any constant value may be used anywhere a constant is allowed, the 65c816 microprocessor must often differentiate between the various types of address expressions. This is particularly true when emitting code since the length of an instruction depends on the particular address expression. If an expression contains only constants, direct page values, absolute values, or long values, there isn't much of a problem. The assembler uses the specified type as the addressing mode. If the expression contains mixed types, the resulting type is as follows: Expression contains: Result is: | | | | +------------+-- Constants - Constant | | +-- Direct | - Direct | +--+ Absolute - Absolute | +--+- Long - Long Allowable forms: constant direct constant+direct absolute constant+absolute long constant+long absolute+long constant+absolute+long This says that if you expression contains only constants, then the result is a constant. If it contains a mixture of constants and direct page addresses, the result is a direct page address. Note that direct page addresses cannot be mixed with other types of addresses. An error must be reported in this situation (although you could get around it with an expression of the form "abs+OFS(direct)"). Likewise, adding a constant to an absolute address produces an absolute address. Adding an absolute and a long address produces a long address, etc. Sometimes, you need to force an expression to be a certain type. For example, the instruction "LDA $200" normally assembles to a load absolute from location $200 in the current data bank. If you need to force this to location $200 in bank zero, regardless of the content of the DBR, the address expression must be coerced to a long address. Coercion of this type is accomplished with the ":D", ":A", ":L", and ":S" expression suffixes. To force "LDA $200" to be assembled using the long address mode, the in- struction is modified to be "LDA $200:L". The coercion suffix must always follow the full address expression. The ":S" (for short branches) suffix is never required, since a short branch (for BRA and BSR) is always assumed, but it is included for completeness. For BRA and BSR, the ":L" suffix is used to imply a long branch (+/- 32K) rather than the long addressing mode. Caveats: If ":D" or ":A" is used to coerce a large address expression to direct or absolute, the high order byte(s) of the expression are truncated and ignored. The assembler must assume that when a programmer uses these constructs he knows exactly what he's doing. Therefore, "LDA $1001:D" will happily assemble this instruction into a "LDA $01" instruction despite the actual value of the address expression. Addressing Mode Specification ----------------------------- 65c816 addressing modes are specified by certain symbols in the op- erand field. A quick rundown follows: Addressing mode Format(s) Example(s) --------------- ------------------ ---------------------- Immediate # LDA #0 = CMP =LastValue Direct Page LDA DPG :D LDA ANY:D Absolute LDA ABS :A LDA ANY:A Long LDA LONG :L LDA ANY:L Accumulator {no operand} ASL INC Implied {no operand} CLC SED Direct, Indirect, Indexed by Y (),Y LDA (DPG),Y ().Y LDA (ANY:D).Y Direct, Indirect, Indexed by Y, Long [],Y LDA [DPG],Y [].Y LDA [DPG].Y Direct, Indexed by X, Indirect (,X) LDA (DPG,X) (.X) LDA (ANY:D.X) Direct, Indexed by X ,X LDA DPG,X .X LDA DPG.X Direct, Indexed by Y ,Y LDX DPG,Y .Y LDX DPG.Y Absolute, Indexed by X ,X LDA ABS,X .X LDA ANY:A.X Long, Indexed by X ,X LDA ANY:L,X .X LDA LONG.X Absolute, Indexed by Y ,Y LDA ANY:A,Y .Y LDA ABS.Y Program Counter Relative (branches) BRA ABS @ BRA @ABS PC Relative (PSH) @ PSH @ABS Absolute, Indirect () JMP (ABS) Absolute, Indexed, Indirect (,X) JMP (ABS,X) (.X) JMP (ABS.X) Direct, Indirect () LDA (DPG) STA (ANY:D) Stack Relative ,S LDA 2,S .S LDA 2.S Stack Relative, Indirect, Indexed (,S),Y LDA (2,S),Y (, MVN LONG,LONG MVP LONG,LONG , DPG- Any direct page expression or symbol. , ABS- Any absolute expression or symbol. , Long- Any long expression or symbol. expr8- Any expression evaluating to a value less than 256. Note: the only real difference between the existing standard and the proposed standard is that the period (".") can be used to form an indexed address ex- pression. This is compatible (in practice, as well as philosophy) with the record structure mechanism supported by this proposed standard. This syntax for the various addressing modes is required at all compliance levels. Suggestion: ():L, ():L,Y, and (], [],Y, and [ .EQU <16-bit value>