'SIMPLE2 - A simple compiler for baseline and midrange PIC chips '(PIC12, PIC16 etc), converts a crude HLL to MPASM/GPASM assembly code. 'Based on SIMPLE from 2001, modified to output stock instructions. 'For QBASIC (must comment cl$), compile to a binary to use command line. 'To compile with FreeBasic do: fbc -e -lang qb simple2.bas ' 'License... 'The simple2 BASIC source code and binary is Copyright 2012 Terry Newton. 'May be redistributed provided the source code is included, the copyright 'remains intact, and any changes are documented with attribution and date. 'The assembly output code may be used for any purpose without restrictions. 'Provided as-is and without warranty. ' 'history... '11/6/2012 initial conversion, changes from 2001 SIMPLE include... ' outputs Microchip instructions instead of Parallax instructions ' bitcopy uses 4 instructions instead of 3 to avoid glitching ' now preserves the case of variable/bit names and other elements ' added raw to output text at column 1 (asm outputs to column 2) ' outputs simple source as comments other than trivial goto byte etc ' preserves trailing ;comments when source line isn't included '11/8/2012 fixed if var <= #constant goto (was always branching) '11/11/2012 fixed to correctly parse constant expressions ending in ")" '11/13/2012 fixed to allow indented asm/raw (previously must be col 1) ' fixed to allow uppercase in bitcopy bit1 = NOT bit2 ' fixed rambase so that uppercase rambase 40H etc works for hex ' fixed to allow specifying array size in hex: array somearray(10H) ' outputs variable EQU's in hex (like 0xAA) instead of decimal ' added code to flip bit if bitcopy bit = not bit and bits are same ' general cleanup to bitcopy and other code/messages DIM ifblock%(10), word$(10), loops%(10), ifelse%(10) title1$ = " A Simple Compiler for PIC12/PIC16 chips " title2$ = " Converts Simple HLL to MPASM/GPASM code " title3$ = " Version 2.02 11/13 Copyright 2012 Terry Newton " asmfilecomment$ = ";compiled by SIMPLE version 2.02" ' uncomment next line for command line parms (comment for QBASIC) cl$ = COMMAND$ IF cl$ = "/?" OR cl$ = "?" OR cl$ = "-?" OR cl$ = "--help" THEN PRINT PRINT title1$: PRINT title2$: PRINT title3$ PRINT " Syntax: SIMPLE [infile[.sim] [outfile[.asm]]]" PRINT PRINT "This compiler does only minimal syntax checking, all assembler and" PRINT "chip-specific stuff must be passed to the assembler using asm lines." PRINT "The assembler itself does the actual parameter and syntax checking," PRINT "if an error occurs, look up the number in the asm file to determine" PRINT "which simple source line caused the error." PRINT "An asm include or other include file (might need UC)" PRINT "must be near the beginning to define the chip being used, refer to" PRINT "the include file for register and bit names. Typically use something" PRINT "like: asm __CONFIG _WDT_OFF & _MCLRE_OFF & _INTRC_OSC_NOCLKOUT & etc" PRINT "to configure chip features, this is specific to the assembler and chip." PRINT "Include asm radix dec near the beginning to default to decimal numbers." PRINT "An asm end at the end of the source is required for most assemblers." PRINT "Use # before immediate constants, decimal numbers are assumed to be" PRINT "constants but precede hex, binary and symbolic constants with #." PRINT "When defining constants, don't use # in the define, just when used." PRINT "Use define symbol = address to reference absolute ram locations." PRINT "Numbers assumed to be decimal, use xxH for hex or xxxxxxxB for binary." PRINT "Parms passed as-is but for bit references '.' is converted to ','." PRINT "Supports up to 9 levels of nested if/then/else or loop/next statements." PRINT PRINT "The Simple language" PRINT "-------------------" PRINT PRINT "byte a define variable a to next ram location (40)" PRINT "define myconst = 10 define myconst to mean 10 decimal" PRINT "define c = 22h define c to mean 22 hex" PRINT "define mybit = c.0 define bit mybit to bit 0 of c" PRINT "array d(8) define d to next ram (41) and allocate 8 bytes" PRINT "rambase 55 set internal ram counter to 55 (or say 37H)" PRINT "byte b define variable b to the next ram (55)" PRINT "a = 1 set variable a to 1 (#1 is ok too)" PRINT "b = #myconst set b to the number defined by myconst" PRINT "!ra = #00001111b set port A direction bits 0-3 to input" PRINT "(no longer supported, use bitset STATUS.RP0 etc to select high regs)" PRINT "c = ra set variable c to port A (use correct name)" PRINT "c = b - a subtracts a from b and stores in c" PRINT "a = a + 10 adds 10 to a" PRINT "a = b and c set a to b AND c (for each bit 1 if both 1)" PRINT "b = b or c set b to b OR c (for each bit 1 if either 1)" PRINT "a = a xor b xor a with b (for each bit 1 if different)" PRINT "c = not a set c to inverse of a (for each bit 1 if 0)" PRINT "a = myarray(c) set a to contents of location myarray+c" PRINT "myarray(5) = 2 set location myarray+5 to the number 2" PRINT "(array elements start at 0, index is added to the base address)" PRINT "if a > b goto label branch if contents of a is greater than b" PRINT "if a < b goto label branch if a is less than b" PRINT "if a >= b goto label branch if a is greater than or equal to b" PRINT "if a <= b goto label branch if a is less than or equal to b" PRINT "if a <> b goto label branch if a is not equal to b" PRINT "if not mybit goto label branch if mybit is clear (not set)" PRINT "if c = #myconst then if contents of c is equal to the number" PRINT " statements defined by myconst, do statement(s)" PRINT "else else is optional, do next statement(s)" PRINT " statements if c is not equal to #myconst" PRINT "endif endif required for blocks, one word." PRINT "(and similar comparison forms, only 2nd parm can be a constant)" PRINT "loop a from 10 set a to 10 (or var) and labels loop point" PRINT " statements statements executed 10 times" PRINT "next a decrease a by 1 and if not 0 loop again" PRINT "increment b same as b = b + 1" PRINT "decrement b same as b = b - 1" PRINT "gosub label call subroutine at label (can be external)" PRINT "goto label branch to label" PRINT "label: internal labels end with :" PRINT "return return from subroutine call" PRINT "shift a left shift bits in a to the left, lsb cleared" PRINT "shift a right shift bits to the right, msb cleared" PRINT "bitset mybit set the bit 'mybit' to 1" PRINT "bitclear mybit clear the bit 'mybit' to 0" PRINT "bitcopy c.0 = mybit copy mybit into bit 0 of variable c" PRINT "bitcopy c.1 = not mybit copy inverse of mybit into bit 1 of c" PRINT "bitcopy mybit = ra.0 copy port A bit 0 into mybit" PRINT "bitcopy mybit = not mybit invert the state of mybit" PRINT "asm line to assemble include assembly instructions (col2+)" PRINT "raw line to assemble pass line directly to assembler (col1)" PRINT "(use raw for directives, formatted assembly w/labels etc)" PRINT "rem comment line comment, included in output" PRINT ";comment line not included in output unless after instr" PRINT SYSTEM END IF infile$ = "": outfile$ = "" IF cl$ <> "" THEN n = INSTR(cl$, " ") IF n = 0 THEN infile$ = cl$ ELSE infile$ = LEFT$(cl$, n - 1) outfile$ = RIGHT$(cl$, LEN(cl$) - n) END IF END IF interactive = 0 IF infile$ = "" THEN PRINT PRINT title1$: PRINT title2$: PRINT title3$ PRINT PRINT " Input file >"; : LINE INPUT infile$ infile$ = LTRIM$(RTRIM$(infile$)) IF infile$ = "" THEN SYSTEM PRINT " Output file >"; : LINE INPUT outfile$ outfile$ = LTRIM$(RTRIM$(outfile$)) IF infile$ = "" THEN SYSTEM PRINT : interactive = 1 END IF IF INSTR(infile$, ".") = 0 THEN infile$ = infile$ + ".sim" IF outfile$ = "" THEN outfile$ = LEFT$(infile$, INSTR(infile$, ".") - 1) + ".asm" END IF IF INSTR(outfile$, ".") = 0 THEN outfile$ = outfile$ + ".asm" IF INSTR(infile$, " ") > 0 OR INSTR(outfile$, " ") THEN PRINT "Filename error or too many parameters": SYSTEM END IF IF UCASE$(infile$) = UCASE$(outfile$) THEN PRINT "Input and output filenames are the same" SYSTEM END IF IF interactive THEN PRINT : PRINT " Compiling "; infile$; " to "; outfile$ PRINT : PRINT END IF GOSUB compile SYSTEM compile: ON ERROR GOTO fileerror OPEN infile$ FOR INPUT AS #1 OPEN outfile$ FOR OUTPUT AS #2 PRINT #2, asmfilecomment$ ON ERROR GOTO cerrtrap comperr = 0: lin = 0: ram = 40: localn = 0: iflevel = 0 FOR i = 0 TO 9: ifblock%(i) = 0: loops%(i) = 0: NEXT i WHILE NOT EOF(1) AND comperr = 0 LINE INPUT #1, raw$: lin = lin + 1 hll$ = LTRIM$(RTRIM$(raw$)) IF hll$ = "" THEN PRINT #2, "": GOTO cnext i = INSTR(hll$, ";") IF i > 0 THEN hll$ = LEFT$(hll$, i - 1) IF hll$ = "" GOTO cnext FOR i = 1 TO 6: word$(i) = "": NEXT i i = 1: sp = 0 parseloop: lp = sp: xp = sp stripspaces: sp = INSTR(xp + 1, hll$, " ") IF MID$(hll$, sp + 1, 1) = " " THEN xp = sp: GOTO stripspaces IF sp = 0 THEN word$(i) = RIGHT$(hll$, LEN(hll$) - lp): GOTO trans word$(i) = MID$(hll$, lp + 1, sp - lp - 1): i = i + 1 IF i < 7 GOTO parseloop trans: FOR i = 1 TO 6: word$(i) = RTRIM$(word$(i)): NEXT i b$ = LCASE$(word$(1)) IF b$ <> "rem" AND b$ <> "asm" AND b$ <> "goto" AND b$ <> "raw" THEN IF RIGHT$(b$, 1) <> ":" AND b$ <> "define" AND b$ <> "byte" THEN PRINT #2, ";"; raw$ END IF END IF IF b$ = "byte" GOTO tbyte IF b$ = "define" GOTO tdefine IF b$ = "array" GOTO tarray IF b$ = "if" GOTO tif IF b$ = "else" GOTO telse IF b$ = "endif" GOTO tendif IF b$ = "goto" GOTO tgoto IF b$ = "gosub" GOTO tgosub IF b$ = "return" GOTO treturn IF b$ = "asm" GOTO tasm IF b$ = "raw" GOTO traw IF b$ = "shift" GOTO tshift IF b$ = "bitset" GOTO tbitset IF b$ = "bitclear" GOTO tbitclear IF b$ = "bitcopy" GOTO tbitcopy IF b$ = "loop" GOTO tloop IF b$ = "next" GOTO tnext IF b$ = "rem" GOTO trem IF b$ = "increment" GOTO tinc IF b$ = "decrement" GOTO tdec IF b$ = "rambase" GOTO trambase IF word$(2) = "=" GOTO tassign IF RIGHT$(word$(1), 1) = ":" GOTO tlabel GOTO cerr tdefine: IF word$(3) <> "=" OR word$(4) = "" GOTO cerr b$ = word$(4): GOSUB fixbit PRINT #2, "#define "; word$(2); " "; b$; z = INSTR(raw$,";"):IF z THEN PRINT #2," ";MID$(raw$,z); PRINT #2,"" GOTO cnext tbyte: IF word$(2) = "" GOTO cerr PRINT #2, word$(2); " EQU 0x"; HEX$(ram);: ram = ram + 1 z = INSTR(raw$,";"):IF z THEN PRINT #2," ";MID$(raw$,z); PRINT #2,"" GOTO cnext tarray: IF word$(2) = "" GOTO cerr a = INSTR(word$(2), "("): IF a = 0 GOTO cerr PRINT #2, LEFT$(word$(2), a - 1); " EQU 0x"; HEX$(ram) a$ = MID$(word$(2), a + 1, LEN(word$(2)) - a - 1) IF LCASE$(RIGHT$(a$,1)) <> "h" THEN ram = ram + VAL(a$) ELSE ram = ram + VAL("&h" + a$) END IF GOTO cnext trambase: IF LCASE$(RIGHT$(word$(2), 1)) <> "h" THEN ram = VAL(word$(2)) ELSE a$ = LEFT$(word$(2), LEN(word$(2)) - 1) ram = VAL("&h" + a$) END IF GOTO cnext tif: b$ = LCASE$(word$(5)) IF b$ = "then" GOTO tbif IF word$(6) = "" GOTO tifbit IF b$ <> "goto" GOTO cerr a$ = "" parm$ = word$(4): GOSUB fiximmediate IF word$(3) = "=" THEN a$ = "cje" IF word$(3) = "<>" THEN a$ = "cjne" IF word$(3) = "<" THEN a$ = "cjb" IF word$(3) = ">" THEN a$ = "cja" IF word$(3) = "<=" THEN a$ = "cjbe" IF word$(3) = ">=" THEN a$ = "cjae" IF a$ = "" GOTO cerr inverted = 0 IF a$ = "cjbe" OR a$ = "cja" THEN IF LEFT$(parm$, 1) = "#" THEN PRINT #2, " MOVLW "; MID$(parm$, 2); "^0xFF" PRINT #2, " ADDWF "; word$(2); ",0" inverted = 1 ELSE PRINT #2, " MOVF "; word$(2); ",0" PRINT #2, " SUBWF "; parm$; ",0" END IF ELSE IF LEFT$(parm$, 1) = "#" THEN PRINT #2, " MOVLW "; MID$(parm$, 2) ELSE PRINT #2, " MOVF "; parm$; ",0" END IF PRINT #2, " SUBWF "; word$(2); ",0" END IF tifp2: IF (a$ = "cja" AND inverted = 0) OR (a$ = "cjbe" AND inverted = 1) OR a$ = "cjb" THEN PRINT #2, " BTFSS 3,0" IF (a$ = "cjbe" AND inverted = 0) OR (a$ = "cja" AND inverted = 1) OR a$ = "cjae" THEN PRINT #2, " BTFSC 3,0" IF a$ = "cje" THEN PRINT #2, " BTFSC 3,2" IF a$ = "cjne" THEN PRINT #2, " BTFSS 3,2" PRINT #2, " GOTO "; word$(6) GOTO cnext tifbit: b$ = LCASE$(word$(2)) c$ = LCASE$(word$(3)) IF b$ = "not" GOTO tifnotbit IF c$ = "then" GOTO tbifbit IF c$ <> "goto" OR word$(4) = "" GOTO cerr b$ = word$(2): GOSUB fixbit PRINT #2, " BTFSC "; b$ PRINT #2, " GOTO "; word$(4) GOTO cnext tifnotbit: b$ = LCASE$(word$(4)) IF b$ = "then" GOTO tbifnotbit IF b$ <> "goto" OR word$(5) = "" GOTO cerr b$ = word$(3): GOSUB fixbit PRINT #2, " BTFSS "; b$ PRINT #2, " GOTO "; word$(5) GOTO cnext ' block if/then/else... oh boy... tbif: a$ = "" parm$ = word$(4): GOSUB fiximmediate IF word$(3) = "=" THEN a$ = "cse" IF word$(3) = "<>" THEN a$ = "csne" IF word$(3) = "<" THEN a$ = "csb" IF word$(3) = ">" THEN a$ = "csa" IF word$(3) = "<=" THEN a$ = "csbe" IF word$(3) = ">=" THEN a$ = "csae" IF a$ = "" GOTO cerr IF iflevel > 9 THEN PRINT "Too many IF statements": GOTO cerr iflevel = iflevel + 1: ifelse%(iflevel) = 0 inverted = 0 IF a$ = "csbe" OR a$ = "csa" THEN IF LEFT$(parm$, 1) = "#" THEN PRINT #2, " MOVLW "; MID$(parm$, 2); "^0xFF" PRINT #2, " ADDWF "; word$(2); ",0" inverted = 1 ELSE PRINT #2, " MOVF "; word$(2); ",0" PRINT #2, " SUBWF "; parm$; ",0" END IF ELSE IF LEFT$(parm$, 1) = "#" THEN PRINT #2, " MOVLW "; MID$(parm$, 2) ELSE PRINT #2, " MOVF "; parm$; ",0" END IF PRINT #2, " SUBWF "; word$(2); ",0" END IF IF (a$ = "csa" AND inverted = 0) OR (a$ = "csbe" AND inverted = 1) OR a$ = "csb" THEN PRINT #2, " BTFSC 3,0" IF (a$ = "csbe" AND inverted = 0) OR (a$ = "csa" AND inverted = 1) OR a$ = "csae" THEN PRINT #2, " BTFSS 3,0" IF a$ = "cse" THEN PRINT #2, " BTFSS 3,2" IF a$ = "csne" THEN PRINT #2, " BTFSC 3,2" PRINT #2, " GOTO ifnext__"; LTRIM$(RTRIM$(STR$(iflevel))); PRINT #2, LTRIM$(RTRIM$(STR$(ifblock%(iflevel)))) GOTO cnext tbifbit: IF iflevel > 9 THEN PRINT "Too many IF statements": GOTO cerr iflevel = iflevel + 1: ifelse%(iflevel) = 0 b$ = word$(2): GOSUB fixbit PRINT #2, " BTFSS "; b$ PRINT #2, " GOTO ifnext__"; LTRIM$(RTRIM$(STR$(iflevel))); PRINT #2, LTRIM$(RTRIM$(STR$(ifblock%(iflevel)))) GOTO cnext tbifnotbit: IF iflevel > 9 THEN PRINT "Too many IF statements": GOTO cerr iflevel = iflevel + 1: ifelse%(iflevel) = 0 b$ = word$(3): GOSUB fixbit PRINT #2, " BTFSC "; b$ PRINT #2, " GOTO ifnext__"; LTRIM$(RTRIM$(STR$(iflevel))); PRINT #2, LTRIM$(RTRIM$(STR$(ifblock%(iflevel)))) GOTO cnext telse: IF iflevel < 1 THEN PRINT "ELSE without IF": GOTO cerr ifelse%(iflevel) = 1 PRINT #2, " GOTO ifend__"; LTRIM$(RTRIM$(STR$(iflevel))); PRINT #2, LTRIM$(RTRIM$(STR$(ifblock%(iflevel)))) PRINT #2, "ifnext__"; LTRIM$(RTRIM$(STR$(iflevel))); PRINT #2, LTRIM$(RTRIM$(STR$(ifblock%(iflevel)))) GOTO cnext tendif: IF iflevel < 1 THEN PRINT "ENDIF without IF": GOTO cerr IF ifelse%(iflevel) = 1 THEN PRINT #2, "ifend__"; LTRIM$(RTRIM$(STR$(iflevel))); ELSE PRINT #2, "ifnext__"; LTRIM$(RTRIM$(STR$(iflevel))); END IF PRINT #2, LTRIM$(RTRIM$(STR$(ifblock%(iflevel)))) ifblock%(iflevel) = ifblock%(iflevel) + 1 iflevel = iflevel - 1 GOTO cnext tgoto: IF word$(2) = "" GOTO cerr PRINT #2, " GOTO "; word$(2); z = INSTR(raw$, ";") IF z THEN PRINT #2, " "; MID$(raw$,z); PRINT #2, "" GOTO cnext tgosub: IF word$(2) = "" GOTO cerr PRINT #2, " CALL "; word$(2) GOTO cnext treturn: PRINT #2, " RETLW 0" GOTO cnext tasm: PRINT #2, " "; MID$(LTRIM$(raw$), 5) GOTO cnext traw: PRINT #2, MID$(LTRIM$(raw$), 5) GOTO cnext tshift: a$ = "" b$ = LCASE$(word$(3)) IF b$ = "left" THEN a$ = "RLF" IF b$ = "right" THEN a$ = "RRF" IF a$ = "" GOTO cerr PRINT #2, " BCF 3,0" PRINT #2, " "; a$; " "; word$(2); ",1" GOTO cnext tbitset: IF word$(2) = "" GOTO cerr b$ = word$(2): GOSUB fixbit PRINT #2, " BSF "; b$ GOTO cnext tbitclear: IF word$(2) = "" GOTO cerr b$ = word$(2): GOSUB fixbit PRINT #2, " BCF "; b$ GOTO cnext tbitcopy: IF word$(3) <> "=" GOTO cerr IF LCASE$(word$(4)) = "not" GOTO tbitnotcopy IF word$(4) = "" GOTO cerr b$ = word$(2): GOSUB fixbit: word$(2) = b$ b$ = word$(4): GOSUB fixbit: word$(4) = b$ PRINT #2, " BTFSS "; word$(4) PRINT #2, " BCF "; word$(2) PRINT #2, " BTFSC "; word$(4) PRINT #2, " BSF "; word$(2) GOTO cnext tbitnotcopy: IF word$(5) = "" GOTO cerr b$ = word$(2): GOSUB fixbit: word$(2) = b$ b$ = word$(5): GOSUB fixbit: word$(5) = b$ IF word$(2) = word$(5) GOTO tbitinvert PRINT #2, " BTFSC "; word$(5) PRINT #2, " BCF "; word$(2) PRINT #2, " BTFSS "; word$(5) PRINT #2, " BSF "; word$(2) GOTO cnext tbitinvert: 'bit flip - must not cross page boundry 'no big deal since if/goto code crossing a page will likely fail anyway PRINT #2, " BTFSC "; word$(2) 'if bit is set PRINT #2, " GOTO $ + 3" ' then skip 2 instructions PRINT #2, " BSF "; word$(2) 'bit clear so set the bit PRINT #2, " GOTO $ + 2" 'skip next instruction PRINT #2, " BCF "; word$(2) 'bit is set so clear the bit GOTO cnext tloop: b$ = LCASE$(word$(3)) IF b$ <> "from" OR word$(4) = "" GOTO cerr parm$ = word$(4): GOSUB fiximmediate IF LEFT$(parm$, 1) = "#" THEN PRINT #2, " MOVLW "; MID$(parm$, 2) ELSE PRINT #2, " MOVF "; parm$; ",0" END IF PRINT #2, " MOVWF "; word$(2) localn = localn + 1 PRINT #2, "local__"; LTRIM$(RTRIM$(STR$(localn))); PRINT #2, LTRIM$(RTRIM$(STR$(loops%(localn)))) GOTO cnext tnext: IF word$(2) = "" GOTO cerr IF localn = 0 THEN PRINT "NEXT without LOOP": GOTO cerr PRINT #2, " DECFSZ "; word$(2); ",1" PRINT #2, " GOTO local__"; LTRIM$(RTRIM$(STR$(localn))); PRINT #2, LTRIM$(RTRIM$(STR$(loops%(localn)))) loops%(localn) = loops%(localn) + 1 localn = localn - 1 GOTO cnext trem: PRINT #2, ";" + raw$ GOTO cnext tlabel: PRINT #2, LEFT$(word$(1), LEN(word$(1)) - 1); z = INSTR(raw$, ";") IF z THEN PRINT #2, " "; MID$(raw$,z); PRINT #2, "" GOTO cnext tassign: IF word$(2) <> "=" OR word$(3) = "" GOTO cerr IF LCASE$(word$(3)) = "not" GOTO tnegate IF word$(4) <> "" GOTO tmath IF RIGHT$(word$(1), 1) = ")" GOTO tarraywrite IF RIGHT$(word$(3), 1) = ")" AND LEFT$(word$(3), 1) <> "#" GOTO tarrayread parm$ = word$(3): GOSUB fiximmediate IF parm$ = "#0" THEN PRINT #2, " CLRF "; word$(1) ELSE IF LEFT$(parm$, 1) = "#" THEN PRINT #2, " MOVLW "; MID$(parm$, 2) ELSE PRINT #2, " MOVF "; parm$; ",0" END IF PRINT #2, " MOVWF "; word$(1) END IF GOTO cnext tmath: IF word$(5) = "" GOTO cerr IF word$(1) = word$(5) GOTO cerr IF word$(1) = word$(3) GOTO tmath2 parm$ = word$(3): GOSUB fiximmediate IF LEFT$(parm$, 1) = "#" THEN PRINT #2, " MOVLW "; MID$(parm$, 2) ELSE PRINT #2, " MOVF "; parm$; ",0" END IF PRINT #2, " MOVWF "; word$(1) tmath2: IF word$(5) = "1" THEN IF word$(4) = "+" THEN PRINT #2, " INCF "; word$(1); ",1": GOTO cnext IF word$(4) = "-" THEN PRINT #2, " DECF "; word$(1); ",1": GOTO cnext END IF a$ = "" b$ = LCASE$(word$(4)) IF b$ = "+" THEN a$ = "add" IF b$ = "-" THEN a$ = "sub" IF b$ = "and" THEN a$ = "and" IF b$ = "or" THEN a$ = "or" IF b$ = "xor" THEN a$ = "xor" IF a$ = "" GOTO cerr parm$ = word$(5): GOSUB fiximmediate IF LEFT$(parm$, 1) = "#" THEN PRINT #2, " MOVLW "; MID$(parm$, 2) ELSE PRINT #2, " MOVF "; parm$; ",0" END IF IF a$ = "add" THEN PRINT #2, " ADDWF "; word$(1); ",1" IF a$ = "sub" THEN PRINT #2, " SUBWF "; word$(1); ",1" IF a$ = "and" THEN PRINT #2, " ANDWF "; word$(1); ",1" IF a$ = "or" THEN PRINT #2, " IORWF "; word$(1); ",1" IF a$ = "xor" THEN PRINT #2, " XORWF "; word$(1); ",1" GOTO cnext tinc: IF word$(2) = "" GOTO cerr PRINT #2, " INCF "; word$(2); ",1" GOTO cnext tdec: IF word$(2) = "" GOTO cerr PRINT #2, " DECF "; word$(2); ",1" GOTO cnext tnegate: IF word$(4) = "" GOTO cerr parm$ = word$(4): GOSUB fiximmediate IF word$(1) = word$(4) GOTO tneg2 IF LEFT$(parm$, 1) = "#" THEN PRINT #2, " MOVLW "; MID$(parm$, 2) ELSE PRINT #2, " MOVF "; parm$; ",0" END IF PRINT #2, " MOVWF "; word$(1) tneg2: PRINT #2, " COMF "; word$(1); ",1" GOTO cnext tarraywrite: a = INSTR(word$(1), "("): IF a = 0 GOTO cerr PRINT #2, " MOVLW "; LEFT$(word$(1), a - 1) PRINT #2, " MOVWF 4" parm$ = MID$(word$(1), a + 1, LEN(word$(1)) - a - 1) GOSUB fiximmediate IF LEFT$(parm$, 1) = "#" THEN PRINT #2, " MOVLW "; MID$(parm$, 2) ELSE PRINT #2, " MOVF "; parm$; ",0" END IF PRINT #2, " ADDWF 4,1" parm$ = word$(3): GOSUB fiximmediate IF LEFT$(parm$, 1) = "#" THEN PRINT #2, " MOVLW "; MID$(parm$, 2) ELSE PRINT #2, " MOVF "; parm$; ",0" END IF PRINT #2, " MOVWF 0" GOTO cnext tarrayread: a = INSTR(word$(3), "("): IF a = 0 GOTO cerr PRINT #2, " MOVLW "; LEFT$(word$(3), a - 1) PRINT #2, " MOVWF 4" parm$ = MID$(word$(3), a + 1, LEN(word$(3)) - a - 1) GOSUB fiximmediate IF LEFT$(parm$, 1) = "#" THEN PRINT #2, " MOVLW "; MID$(parm$, 2) ELSE PRINT #2, " MOVF "; parm$; ",0" END IF PRINT #2, " ADDWF 4,1" PRINT #2, " MOVF 0,0" PRINT #2, " MOVWF "; word$(1) GOTO cnext cerr: comperr = 1 PRINT "Error compiling line "; lin cnext: WEND CLOSE IF comperr THEN KILL outfile$ RETURN fiximmediate: IF VAL(parm$) > 0 OR parm$ = "0" THEN parm$ = "#" + parm$ RETURN fixbit: FOR z = 1 TO LEN(b$) IF MID$(b$, z, 1) = "." THEN MID$(b$, z, 1) = "," NEXT z RETURN cerrtrap: PRINT "Major error" CLOSE : SYSTEM fileerror: PRINT "File not found" CLOSE : SYSTEM