rscid = "$Header$" EM_WSIZE=2 EM_PSIZE=2 EM_BSIZE=4 SL=4 FORMAT = "0%o" TIMEFACTOR = 1/300 illins = "Illegal" PROPERTIES GENREG /* All PDP registers */ REG /* Normal registers (allocatable) */ ODDREG /* All odd registers (allocatable) */ REGPAIR(4) /* Register pairs for division */ FLTREG(4) /* Floating point registers, single precision */ DBLREG(8) /* Same, double precision */ GENFREG(4) /* generic floating point */ GENDREG(8) /* generic floating point */ FLTREGPAIR(8) /* register pair for modf */ DBLREGPAIR(16) /* same, double precision */ LOCALBASE /* Guess what */ STACKPOINTER PROGRAMCOUNTER REGISTERS r0 : GENREG,REG. r2,r4 : GENREG,REG regvar. r1,r3 : GENREG,REG,ODDREG. r01("r0")=r0+r1 : REGPAIR. fr0("r0"),fr1("r1"),fr2("r2"),fr3("r3") : GENFREG,FLTREG. dr0("r0")=fr0,dr1("r1")=fr1,dr2("r2")=fr2,dr3("r3")=fr3 : GENDREG,DBLREG. fr01("r0")=fr0+fr1,fr23("r2")=fr2+fr3 : FLTREGPAIR. dr01("r0")=dr0+dr1,dr23("r2")=dr2+dr3 : DBLREGPAIR. lb("r5") : GENREG,LOCALBASE. sp : GENREG,STACKPOINTER. pc : GENREG,PROGRAMCOUNTER. TOKENS const2 = { INT num; } 2 "$" num . LOCAL = { INT ind; INT size; } 2 ind "(r5)" . ILOCAL = { INT ind; } 2 "*" ind "(r5)" . DLOCAL = { INT ind; INT size; } 4 ind "(r5)" . addr_local = { INT ind; } 2 . addr_external = { ADDR off; } 2 "$" off. regdef2 = { GENREG reg; } 2 "*" reg. regind2 = { GENREG reg; ADDR off; } 2 off "(" reg ")" . reginddef2 = { GENREG reg; ADDR off; } 2 "*" off "(" reg ")" . regconst2 = { GENREG reg; ADDR off; } 2 . relative2 = { ADDR off; } 2 off . reldef2 = { ADDR off; } 2 "*" off. regdef1 = { GENREG reg; } 2 "*" reg. regind1 = { GENREG reg; ADDR off; } 2 off "(" reg ")" . reginddef1 = { GENREG reg; ADDR off; } 2 "*" off "(" reg ")" . relative1 = { ADDR off; } 2 off. reldef1 = { ADDR off; } 2 "*" off. autodec = { GENREG reg; } 2 "-(" reg ")". autoinc = { GENREG reg; } 2 "(" reg ")+". ftoint = { GENFREG reg; } 2 . ftolong = { GENFREG reg; } 4 . regind4 = { GENREG reg; ADDR off; } 4 off "(" reg ")". reginddef4 = { GENREG reg; ADDR off; } 4 "*" off "(" reg ")". relative4 = { ADDR off; } 4 off. reldef4 = { ADDR off; } 4 "*" off. regdef4 = { GENREG reg; } 4 "*" reg. regind8 = { GENREG reg; ADDR off; } 8 off "(" reg ")". reginddef8 = { GENREG reg; ADDR off; } 8 "*" off "(" reg ")". relative8 = { ADDR off; } 8 off. reldef8 = { ADDR off; } 8 "*" off. regdef8 = { GENREG reg; } 8 "*" reg. label = { ADDR off; } 2 off. SETS src2 = GENREG + regdef2 + regind2 + reginddef2 + relative2 + reldef2 + addr_external + const2 + LOCAL + ILOCAL + autodec + autoinc . dst2 = src2 - ( const2 + addr_external ) . xsrc2 = src2 + ftoint . src1 = regdef1 + regind1 + reginddef1 + relative1 + reldef1 . dst1 = src1 . src1or2 = src1 + src2 . src4 = relative4 + regdef4 + DLOCAL + regind4 . dst4 = src4 . long4 = src4 + REGPAIR . longf4 = src4 + reldef4 + reginddef4 + FLTREG . f4src = longf4 + autoinc + autodec . f4dst = f4src . long8 = relative8 + regdef8 + regind8 + DBLREG . double8 = long8 + reldef8 + reginddef8 . freg = FLTREG + DBLREG . fsrc = FLTREG + double8 + autoinc + autodec . fdst = fsrc . indexed2 = regind2 + reginddef2 . indexed4 = regind4 . indexed8 = regind8 . indexed = indexed2 + indexed4 + indexed8 . regdeferred = regdef2 + regdef4 + regdef8 . indordef = indexed + regdeferred . locals = LOCAL + DLOCAL . variable2 = relative2 + reldef2 . variable4 = relative4 . variable8 = relative8 . variable = variable2 + variable4 + variable8 . regs = REG + REGPAIR + FLTREG + DBLREG . noconst2 = src2 - const2 - addr_external . allexeptcon = ALL - ( regs + const2 + addr_local + addr_external ) . externals = relative1 + relative2 + relative4 + relative8 . posextern = variable + regdeferred + indexed + externals . diradr2 = regconst2 + addr_external . INSTRUCTIONS /* default cost */ cost(2,450) /* Normal instructions */ adc dst2:rw:cc . add src2:ro,dst2:rw:cc . ash src2:ro,REG:rw:cc . ashc src2:ro,REGPAIR+ODDREG:rw kills :cc . asl dst2:rw:cc . asr dst2:rw:cc . bxx "syntax error" label . /* generic branch used only as bxx* */ bcc label . bcs label . beq label . bge label . bgt label . bhi label . bhis "bcc" label . bic src2:ro,dst2:rw:cc . bis src2:ro,dst2:rw:cc . bisb src1or2:ro,REG:rw kills :cc . bit src2:ro,src2:ro kills :cc. ble label . blo "bcs" label . blos label . blt label . bmi label . bne label . bpl label . br label . bvc label . bvs label . clr dst2:wo:cc . clrb dst1:wo kills :cc . cmp src2:ro,src2:ro kills :cc . cmpb src1or2:ro,src1or2:ro kills :cc . com dst2:rw:cc . dec dst2:rw:cc . div src2:ro,REG:rw kills :cc . inc dst2:rw:cc . jbr label . jeq label . jne label . jxx "syntax error" label . jmp dst2+label . jsr GENREG:rw,dst2+label kills :cc. mov src2:ro,dst2:wo:cc . movb src1or2:ro,dst1+REG:wo kills :cc . mul src2:ro,ODDREG:rw:cc . neg dst2:rw:cc . rol dst2:rw:cc . ror dst2:rw:cc . rts GENREG:rw . sbc dst2:rw:cc . sob REG:rw,label . sub src2:ro,dst2:rw:cc . sxt dst2:wo . tst src2:ro:cc . xor REG:ro,dst2:rw:cc . /* floating point instructions */ cfcc . setf . setd . seti . setl . clrf fdst. negf fdst . absf fdst . tstf fsrc . movf fsrc,freg . movf freg,fdst . movif src2,freg . movif src4,freg . movfi freg,dst2 . movfi freg,dst4 . movof f4src,freg . movfo freg,f4dst . movie src2,freg . movei freg,dst2 . addf fsrc,freg . subf fsrc,freg . mulf fsrc,freg . divf fsrc,freg . cmpf fsrc,freg . modf fsrc,FLTREGPAIR+DBLREGPAIR . ldfps src2 . stfps dst2 . stst dst2 . /* weirdo instructions */ mfpt kills r0 . MOVES from const2 %num==0 to dst2 gen clr %2 from src2 to dst2 gen mov %1,%2 from FLTREG to longf4-FLTREG gen movfo %1,%2 from longf4-FLTREG to FLTREG gen movof %1,%2 from FLTREG to FLTREG gen movf %1,%2 from DBLREG to double8 gen movf %1,%2 from double8 to DBLREG gen movf %1,%2 from const2 %num==0 to src1 gen clrb %2 from src1or2 to src1 gen movb %1,%2 from ftoint to dst2 gen movfi %1.reg,%2 TESTS to test src2 gen tst %1 STACKINGRULES from const2 %num==0 to STACK gen clr {autodec,sp} from src2 to STACK gen mov %1,{autodec,sp} from regconst2 to STACK gen mov %1.reg,{autodec,sp} add {addr_external, %1.off},{regdef2,sp} from addr_local to STACK gen mov lb,{autodec,sp} add {const2, %1.ind},{regdef2,sp} from DBLREG to STACK gen movf %1,{autodec,sp} from FLTREG to STACK gen movfo %1,{autodec,sp} from REGPAIR to STACK gen mov %1.2,{autodec,sp} mov %1.1,{autodec,sp} from regind4 to STACK gen mov {regind2, %1.reg, 2+%1.off},{autodec,sp} mov {regind2, %1.reg, %1.off},{autodec,sp} from relative4 to STACK gen mov {relative2, 2+%1.off},{autodec,sp} mov {relative2, %1.off},{autodec,sp} from regdef4 to STACK gen mov {regind2, %1.reg, 2},{autodec,sp} mov {regdef2, %1.reg },{autodec,sp} from regind8 to STACK uses REG gen move %1.reg,%a add {addr_external, 8+%1.off},%a mov {autodec, %a},{autodec,sp} mov {autodec, %a},{autodec,sp} mov {autodec, %a},{autodec,sp} mov {autodec, %a},{autodec,sp} from regind8 to STACK gen mov {regind2, %1.reg, 6+%1.off},{autodec,sp} mov {regind2, %1.reg, 4+%1.off},{autodec,sp} mov {regind2, %1.reg, 2+%1.off},{autodec,sp} mov {regind2, %1.reg, %1.off},{autodec,sp} from relative8 to STACK uses REG gen mov {addr_external, 8+%1.off},%a mov {autodec, %a},{autodec,sp} mov {autodec, %a},{autodec,sp} mov {autodec, %a},{autodec,sp} mov {autodec, %a},{autodec,sp} from relative8 to STACK gen mov {relative2, 6+%1.off},{autodec,sp} mov {relative2, 4+%1.off},{autodec,sp} mov {relative2, 2+%1.off},{autodec,sp} mov {relative2, %1.off},{autodec,sp} from regdef8 to STACK gen mov {regind2, %1.reg, 6},{autodec,sp} mov {regind2, %1.reg, 4},{autodec,sp} mov {regind2, %1.reg, 2},{autodec,sp} mov {regdef2, %1.reg },{autodec,sp} from DLOCAL to STACK gen mov {LOCAL, 2+%1.ind, 2},{autodec,sp} mov {LOCAL, %1.ind, 2},{autodec,sp} from src1 to STACK gen clr {autodec,sp} movb %1,{regdef1,sp} from ftoint to STACK gen movfi %1.reg,{autodec,sp} from ftolong to STACK gen setl. movfi %1.reg,{autodec,sp} seti. COERCIONS from STACK uses REG gen mov {autoinc,sp},%a yields %a from STACK uses REG gen mov {autoinc,sp},%a yields {regconst2, %a, 0} from STACK uses FLTREG gen movof {autoinc,sp},%a yields %a from STACK uses DBLREG gen movf {autoinc,sp},%a yields %a from STACK uses REGPAIR gen mov {autoinc,sp},%a.1 mov {autoinc,sp},%a.2 yields %a from LOCAL yields {regind2,lb,%1.ind} from DLOCAL yields {regind4,lb,%1.ind} from regconst2 uses reusing %1,REG=%1.reg gen add {addr_external, %1.off},%a yields %a from addr_local uses REG gen mov lb,%a add {const2, %1.ind},%a yields %a from REG yields {regconst2, %1, 0} from xsrc2 uses reusing %1, REG=%1 yields %a from xsrc2 uses reusing %1, REG=%1 yields {regconst2, %a, 0} from longf4 uses FLTREG gen move %1,%a yields %a from double8 uses DBLREG gen move %1,%a yields %a from src1 uses REG={const2,0} gen bisb %1,%a yields %a from REGPAIR yields %1.2 %1.1 from regind4 yields {regind2,%1.reg,2+%1.off} {regind2,%1.reg,%1.off} from relative4 yields {relative2,2+%1.off} {relative2,%1.off} from regdef4 yields {regind2,%1.reg,2} {regdef2,%1.reg} from DLOCAL yields {LOCAL, %1.ind+2, 2} {LOCAL, %1.ind, 2} /******************************** * from double8 to long4 * ********************************/ from regind8 yields {regind4,%1.reg,4+%1.off} {regind4,%1.reg,%1.off} from relative8 yields {relative4,4+%1.off} {relative4,%1.off} from regdef8 yields {regind4,%1.reg,4} {regdef4,%1.reg} PATTERNS /******************************************************** * Group 1 : load instructions. * * * * For most load instructions no code is generated. * * Action : put something on the fake-stack. * ********************************************************/ pat loc yields {const2, $1} pat ldc yields {const2, loww($1)} {const2, highw($1)} pat lol yields {LOCAL, $1,2} pat loe yields {relative2, $1} pat lil yields {ILOCAL, $1} pat lof with REG yields {regind2,%1,$1} with exact regconst2 yields {regind2,%1.reg,$1+%1.off} with exact addr_external yields {relative2,$1+%1.off} with exact addr_local yields {LOCAL, %1.ind + $1,2} pat lal yields {addr_local, $1} pat lae yields {addr_external, $1} pat lpb leaving adp SL pat lxl $1==0 yields lb pat lxl $1==1 yields {LOCAL ,SL,2} pat lxl $1==2 uses REG={LOCAL, SL, 2} yields {regind2,%a, SL} pat lxl $1==3 uses REG={LOCAL, SL, 2} gen move {regind2,%a, SL},%a yields {regind2,%a, SL} pat lxl $1>3 uses REG={LOCAL, SL, 2}, REG={const2,$1-1} gen 1: move {regind2,%a, SL},%a sob %b,{label,1b} yields %a pat lxa $1==0 yields {addr_local, SL} pat lxa $1==1 uses REG={LOCAL, SL, 2 } yields {regconst2, %a, SL } pat lxa $1==2 uses REG={LOCAL, SL, 2 } gen move {regind2, %a, SL }, %a yields {regconst2, %a, SL } pat lxa $1==3 uses REG={LOCAL, SL, 2 } gen move {regind2, %a, SL }, %a move {regind2, %a, SL }, %a yields {regconst2, %a, SL } pat lxa $1 > 3 uses REG={LOCAL, SL, 2}, REG={const2,$1-1} gen 1: move {regind2,%a, SL},%a sob %b,{label,1b} yields {regconst2, %a, SL } pat dch leaving loi 2 pat loi $1==2 with REG yields {regdef2, %1} with exact regconst2 yields {regind2, %1.reg, %1.off} with exact relative2 yields {reldef2, %1.off} with exact regind2 yields {reginddef2, %1.reg, %1.off} with exact regdef2 yields {reginddef2, %1.reg, 0} with exact addr_local yields {LOCAL, %1.ind,2} with exact addr_external yields {relative2, %1.off} with exact LOCAL yields {reginddef2, lb, %1.ind} pat loi $1==1 with REG yields {regdef1, %1} with exact regconst2 yields {regind1, %1.reg, %1.off} with exact addr_external yields {relative1, %1.off} with exact addr_local yields {regind1, lb, %1.ind} with exact relative2 yields {reldef1, %1.off} with exact regind2 yields {reginddef1, %1.reg, %1.off} with exact regdef2 yields {reginddef1, %1.reg, 0} with exact LOCAL yields {reginddef1, lb, %1.ind} pat loi $1==4 with REG yields {regdef4, %1} with exact regconst2 yields {regind4, %1.reg, %1.off} with exact addr_local yields {DLOCAL,%1.ind,4} with exact addr_external yields {relative4, %1.off} pat loi $1==8 with REG yields {regdef8, %1} with exact regconst2 yields {regind8, %1.reg, %1.off} with exact addr_local yields {regind8, lb , %1.ind} with exact addr_external yields {relative8, %1.off} pat loi with exact addr_local kills ALL uses REG={const2,$1/2}, REG gen move lb,%b add {const2,%1.ind+$1},%b 1: mov {autodec,%b},{autodec,sp} sob %a,{label,1b} with exact addr_external kills ALL uses REG={const2,$1/2}, REG gen mov {addr_external,%1.off+$1},%b 1: mov {autodec,%b},{autodec,sp} sob %a,{label,1b} with REG kills ALL uses REG={const2,$1} gen add %a,%1 asr %a 1: mov {autodec,%1},{autodec,sp} sob %a,{label,1b} pat ldl yields {DLOCAL, $1,4} pat lde yields {relative4, $1} pat ldf with regconst2 yields {regind4,%1.reg,$1+%1.off} with exact addr_external yields {relative4, $1+%1.off} with exact addr_local yields {DLOCAL, %1.ind+$1,4} pat lpi yields {addr_external, $1} /**************************************************************** * Group 2 : Store instructions. * * * * These instructions are likely to ruin the fake-stack. * * We don't expect many items on the fake-stack anyway * * because we seem to have evaluated an expression just now. * ****************************************************************/ pat stl with xsrc2 kills indordef, locals %ind <= $1 && %ind+%size > $1 gen move %1,{LOCAL,$1,2} pat ste with xsrc2 kills posextern gen move %1, {relative2, $1 } pat sil with xsrc2 kills allexeptcon gen move %1, {reginddef2,lb,$1} pat stf with regconst2 xsrc2 kills allexeptcon gen move %2,{regind2,%1.reg,$1+%1.off} with addr_external xsrc2 kills allexeptcon gen move %2,{relative2,$1+%1.off} pat sti $1==2 with REG xsrc2 kills allexeptcon gen move%2,{regdef2,%1} with regconst2 xsrc2 kills allexeptcon gen move%2,{regind2,%1.reg,%1.off} with addr_external xsrc2 kills allexeptcon gen move %2,{relative2,%1.off} with addr_local xsrc2 kills allexeptcon gen move %2,{LOCAL, %1.ind, 2} with relative2 xsrc2 kills allexeptcon gen move %2,{reldef2,%1.off} with regind2 xsrc2 kills allexeptcon gen move %2,{reginddef2,%1.reg,%1.off} pat sti $1==1 with REG src1or2 kills allexeptcon gen move %2,{regdef1,%1} with exact regconst2 src1or2 kills allexeptcon gen move %2,{regind1,%1.reg,%1.off} with exact addr_external src1or2 kills allexeptcon gen move %2,{relative1,%1.off} with exact addr_local src1or2 kills allexeptcon gen move %2,{regind1, lb, %1.ind} with exact relative2 src1or2 kills allexeptcon gen move %2,{reldef1,%1.off} with exact regind2 src1or2 kills allexeptcon gen move %2,{reginddef1,%1.reg,%1.off} pat sti $1==4 with exact REG FLTREG kills allexeptcon gen movfo %2,{regdef4,%1} with exact regind2 FLTREG kills allexeptcon gen movfo %2,{reginddef4,%1.reg,%1.off} with exact relative2 FLTREG kills allexeptcon gen movfo %2,{reldef4,%1.off} with exact REG ftolong kills allexeptcon gen setl. movfi %2.reg,{regdef2,%1} seti. with exact regind2 ftolong kills allexeptcon gen setl. movfi %2.reg,{reginddef2,%1.reg,%1.off} seti. with exact relative2 ftolong kills allexeptcon gen setl. movfi %2.reg,{reldef2,%1.off} seti. with exact regconst2 FLTREG kills allexeptcon gen movfo %2,{regind4,%1.reg,%1.off} with exact regconst2 ftolong kills allexeptcon gen setl. movfi %2.reg,{regind2,%1.reg,%1.off} seti. with exact addr_local FLTREG kills allexeptcon gen movfo %2,{DLOCAL,%1.ind,4} with exact addr_local ftolong kills allexeptcon gen setl. movfi %2.reg,{DLOCAL,%1.ind,4} seti. with exact addr_external FLTREG kills allexeptcon gen movfo %2,{relative4,%1.off} with exact addr_external ftolong kills allexeptcon gen setl. movfi %2.reg,{relative2,%1.off} seti. with REG src2 src2 kills allexeptcon gen move %2,{regdef2,%1} move %3,{regind2,%1,2} with REG STACK gen mov {autoinc,sp},{autoinc,%1} mov {autoinc,sp},{regdef2,%1} pat sti $1==8 with exact REG DBLREG kills allexeptcon gen movf %2,{regdef8,%1} with exact regind2 DBLREG kills allexeptcon gen movf %2,{reginddef8,%1.reg,%1.off} with exact relative2 DBLREG kills allexeptcon gen movf %2,{reldef8,%1.off} with exact regconst2 DBLREG kills allexeptcon gen movf %2,{regind8,%1.reg,%1.off} with exact addr_local DBLREG kills allexeptcon gen movf %2,{regind8, lb, %1.ind} with exact addr_external DBLREG kills allexeptcon gen movf %2,{relative8, %1.off} with REG regind8 kills allexeptcon gen mov {regind2,%2.reg,%2.off },{autoinc,%1} mov {regind2,%2.reg,%2.off+2},{autoinc,%1} mov {regind2,%2.reg,%2.off+4},{autoinc,%1} mov {regind2,%2.reg,%2.off+6},{regdef2,%1} with REG relative8 kills allexeptcon uses REG={addr_external,%2.off} gen mov {autoinc,%a},{autoinc,%1} mov {autoinc,%a},{autoinc,%1} mov {autoinc,%a},{autoinc,%1} mov {regdef2,%a},{regdef2,%1} with REG STACK gen mov {autoinc,sp},{autoinc,%1} mov {autoinc,sp},{autoinc,%1} mov {autoinc,sp},{autoinc,%1} mov {autoinc,sp},{regdef2,%1} pat sti with REG STACK uses REG={const2,$1/2} gen 1: mov {autoinc,sp},{autoinc,%1} sob %a,{label,1b} pat lal sti $2>2 && $2<=8 with exact xsrc2 yields %1 leaving stl $1 lal $1+2 sti $2-2 with yields {addr_local,$1} leaving sti $2 pat sdl with exact FLTREG kills indordef, locals %ind <= $1+2 && %ind+%size > $1 gen move %1,{DLOCAL,$1,4} with exact ftolong kills indordef, locals %ind <= $1+2 && %ind+%size > $1 gen setl. movfi %1.reg,{DLOCAL,$1,4} seti. with src2 src2 kills indordef, locals %ind <= $1+2 && %ind+%size > $1 gen move %1,{LOCAL,$1,2} move %2,{LOCAL,$1+2,2} pat sde with exact FLTREG kills posextern gen move %1,{relative4,$1} with exact ftolong kills posextern gen setl. movfi %1.reg,{relative4,$1} seti. with src2 src2 kills posextern gen move %1, {relative2, $1 } move %2, {relative2, $1+2} pat sdf with exact regconst2 FLTREG kills allexeptcon gen move %2,{regind4,%1.reg,$1+%1.off} with exact regconst2 ftolong kills allexeptcon gen setl. movfi %2.reg,{regind4,%1.reg,$1+%1.off} seti. with exact addr_external FLTREG kills allexeptcon gen move %2,{relative4,$1+%1.off} with exact addr_external ftolong kills allexeptcon gen setl. movfi %2.reg,{relative4, $1+%1.off} seti. with regconst2 src2 src2 kills allexeptcon gen move %2,{regind2,%1.reg,$1+%1.off} move %3,{regind2,%1.reg,$1+2+%1.off} with addr_external src2 src2 kills allexeptcon gen move %2,{relative2,$1+%1.off} move %3,{relative2,$1+2+%1.off} /**************************************************************** * Group 3 : Integer arithmetic. * * * * Implemented (sometimes with the use of subroutines) : * * all 2 and 4 byte arithmetic. * ****************************************************************/ pat adi $1==2 with exact REG const2 yields {regconst2,%1,%2.num} with exact REG addr_external yields {regconst2,%1,%2.off} with exact REG addr_local gen add lb,%1 yields {regconst2,%1,%2.ind} with exact REG addr_local uses REG gen mov lb,%a add %1,%a yields {regconst2,%a,%2.ind} with exact REG regconst2 gen add %2.reg,%1 yields {regconst2,%1,%2.off} with exact src2-REG const2+addr_external+addr_local uses reusing %1,REG=%1 yields %2 %a leaving adi 2 with exact regconst2 const2 yields {regconst2,%1.reg,%2.num+%1.off} with exact regconst2 addr_external yields {regconst2,%1.reg,%2.off+%1.off} with exact regconst2 addr_local gen add lb,%1.reg yields {regconst2,%1.reg,%2.ind+%1.off} with exact regconst2 regconst2 gen add %2.reg,%1.reg yields {regconst2,%1.reg,%2.off+%1.off} with exact regconst2 noconst2 gen add %2,%1.reg yields %1 with exact REG noconst2 gen add %2,%1 yields %1 with exact src2 regconst2 gen add %1,%2.reg yields %2 with exact regconst2 src2 gen add %2,%1.reg yields %1 with src2 REG gen add %1,%2 yields %2 pat adi $1==4 with REG REG src2 src2 gen add %4,%2 adc %1 add %3,%1 yields %2 %1 with REG REG src2 STACK gen add {autoinc,sp},%2 adc %1 add %3,%1 yields %2 %1 with REG REG STACK gen add {autoinc,sp},%1 add {autoinc,sp},%2 adc %1 yields %2 %1 with src2 src2 REG REG gen add %2,%4 adc %3 add %1,%3 yields %4 %3 pat sbi $1==2 with src2 REG gen sub %1,%2 yields %2 with exact REG src2-REG gen sub %2,%1 neg %1 yields %1 pat sbi $1==4 with src2-REG src2-REG REG REG gen sub %2,%4 sbc %3 sub %1,%3 yields %4 %3 with src2 src2 STACK gen sub %2,{regind2,sp,2} sbc {regdef2,sp} sub %1,{regdef2,sp} pat mli $1==2 with ODDREG src2 gen mul %2,%1 yields %1 with src2 ODDREG gen mul %1,%2 yields %2 pat mli $1==4 with STACK gen jsr pc,{label, "mli4~"} yields r1 r0 pat dvi $1==2 with src2 src2 uses reusing %2,REGPAIR gen mov %2,%a.2 sxt %a.1 div %1,%a.1 yields %a.1 with src2 src2 STACK gen mov %1,{autodec,sp} mov %2,r1 sxt r0 div {autoinc,sp},r0 yields r0 pat dvi $1==4 with STACK gen jsr pc,{label, "dvi4~"} yields r1 r0 pat rmi $1==2 with src2 src2 uses reusing %2,REGPAIR gen mov %2,%a.2 sxt %a.1 div %1,%a.1 yields %a.2 with src2 src2 STACK gen mov %1,{autodec,sp} mov %2,r1 sxt r0 div {autoinc,sp},r0 yields r1 pat rmi $1==4 with STACK gen jsr pc,{label, "rmi4~"} yields r1 r0 pat ngi $1==2 with REG gen neg %1 yields %1 pat ngi $1==4 with REG REG gen neg %1 neg %2 sbc %1 yields %2 %1 pat loc sli $1==1 && $2==2 with REG gen asl %1 yields %1 pat sli $1==2 with src2 REG gen ash %1,%2 yields %2 pat sli $1==4 with src2 REGPAIR gen ashc %1,%2 yields %2 pat loc sri $1==1 && $2==2 with REG gen asr %1 yields %1 pat loc sri $2==2 with REG gen ash {const2,0-$1},%1 yields %1 pat sri $1==2 with REG REG gen neg %1 ash %1,%2 yields %2 pat loc sri $2==4 with REGPAIR gen ashc {const2,0-$1},%1 yields %1 pat sri $1==4 with REG REGPAIR gen neg %1 ashc %1,%2 yields %2 /************************************************ * Group 4 : unsigned arithmetic * * * * adu = adi * * sbu = sbi * * slu = sli * * * * Supported : 2- and 4 byte arithmetic. * ************************************************/ pat adu leaving adi $1 pat sbu leaving sbi $1 pat mlu $1==2 leaving mli 2 pat mlu $1==4 with STACK gen jsr pc,{label, "mlu4~"} yields r1 r0 pat dvu $1==2 with STACK gen jsr pc,{label, "dvu2~"} yields r0 pat dvu $1==4 with STACK gen jsr pc,{label, "dvu4~"} yields r1 r0 pat rmu $1==2 with STACK gen jsr pc,{label, "rmu2~"} yields r1 pat rmu $1==4 with STACK gen jsr pc,{label, "rmu4~"} yields r1 r0 pat slu leaving sli $1 pat sru $1==2 with REG xsrc2 uses reusing %2,REGPAIR gen move %2,%a.2 move {const2,0},%a.1 neg %1 ashc %1,%a yields %a.2 pat loc sru $2==2 with xsrc2 uses reusing %1,REGPAIR gen move %1,%a.2 move {const2,0},%a.1 ashc {const2,0-$1},%a yields %a.2 pat sru $1==4 with STACK gen move {const2,$1},r0 jsr pc,{label, "sru~"} /************************************************ * Group 5 : Floating point arithmetic * * * * Supported : 4- and 8 byte arithmetic. * ************************************************/ pat adf $1==4 with FLTREG FLTREG gen addf %1,%2 yields %2 with FLTREG FLTREG gen addf %2,%1 yields %1 pat adf $1==8 with double8 DBLREG gen addf %1,%2 yields %2 with DBLREG double8 gen addf %2,%1 yields %1 pat sbf $1==4 with FLTREG FLTREG gen subf %1,%2 yields %2 pat sbf $1==8 with double8 DBLREG gen subf %1,%2 yields %2 pat mlf $1==4 with FLTREG FLTREG gen mulf %1,%2 yields %2 with FLTREG FLTREG gen mulf %2,%1 yields %1 pat mlf $1==8 with double8 DBLREG gen mulf %1,%2 yields %2 with DBLREG double8 gen mulf %2,%1 yields %1 pat dvf $1==4 with FLTREG FLTREG gen divf %1,%2 yields %2 pat dvf $1==8 with double8 DBLREG gen divf %1,%2 yields %2 pat ngf $1==4 with FLTREG gen negf %1 yields %1 pat ngf $1==8 with DBLREG gen negf %1 yields %1 pat fif $1==4 with longf4 FLTREG uses FLTREGPAIR gen move %1,%a.1 modf %2,%a yields %a.1 %a.2 pat fif $1==8 with double8 double8 uses DBLREGPAIR gen move %1,%a.1 modf %2,%a yields %a.1 %a.2 pat fef $1==4 with FLTREG uses REG gen movei %1,%a movie {const2,0},%1 yields %1 %a pat fef $1==8 with DBLREG uses REG gen movei %1,%a movie {const2,0},%1 yields %1 %a /**************************************** * Group 6 : pointer arithmetic. * * * * Pointers have size 2 bytes. * ****************************************/ pat adp with REG yields {regconst2, %1, $1} with exact regconst2 yields {regconst2, %1.reg, $1+%1.off} with exact addr_external yields {addr_external, $1+%1.off} with exact addr_local yields {addr_local,%1.ind+$1} pat ads $1==2 leaving adi 2 pat sbs $1==2 leaving sbi $1 /**************************************** * Group 7 : increment/decrement/zero * ****************************************/ pat inc with REG gen inc %1 yields %1 pat inl kills indordef, locals %ind <= $1 && %ind+%size > $1 gen inc {LOCAL,$1,2} pat ine kills posextern gen inc {relative2, $1} pat dec with REG gen dec %1 yields %1 pat del kills indordef, locals %ind <= $1 && %ind+%size > $1 gen dec {LOCAL, $1, 2} pat dee kills posextern gen dec {relative2, $1} pat lol loc sbi stl $1==$4 && $3==2 kills indordef, locals %ind <= $1 && %ind+%size > $1 gen sub {const2,$2},{LOCAL,$1,2} pat lol ngi stl $1==$3 && $2==2 kills indordef, locals %ind <= $1 && %ind+%size > $1 gen neg {LOCAL, $1, 2} pat lil ngi sil $1==$3 && $2==2 kills allexeptcon gen neg {ILOCAL, $1} pat lil inc sil $1==$3 kills allexeptcon gen inc {ILOCAL, $1} pat lol adi stl $2==2 && $1==$3 with src2 kills indordef, locals %ind <= $1 && %ind+%size > $1 gen add %1,{LOCAL, $1, 2} pat lol adp stl $1==$3 && $2==1 kills indordef, locals %ind <= $1 && %ind+%size > $1 gen inc {LOCAL, $1, 2} pat lol adp stl $1==$3 kills indordef, locals %ind <= $1 && %ind+%size > $1 gen add {const2, $2},{LOCAL, $1, 2} pat loe adi ste $2==2 && $1==$3 with src2 kills posextern gen add %1,{relative2, $1} pat loe adp ste $1==$3 kills posextern gen add {const2, $2},{relative2, $1} pat lol ior stl $2==2 && $1==$3 with src2 kills indordef, locals %ind <= $1 && %ind+%size > $1 gen bis %1,{LOCAL, $1, 2} pat loe ior ste $2==2 && $1==$3 with src2 kills posextern gen bis %1,{relative2, $1} pat lol and stl $2==2 && $1==$3 with REG kills indordef, locals %ind <= $1 && %ind+%size > $1 gen com %1 bic %1,{LOCAL, $1, 2} pat loe and ste $2==2 && $1==$3 with REG kills posextern gen com %1 bic %1,{relative2, $1} pat loc lol and stl $3==2 && $2==$4 kills indordef, locals %ind <= $2 && %ind+%size > $2 gen bic {const2, ~$1},{LOCAL, $2, 2} pat loc loe and ste $3==2 && $2==$4 kills posextern gen bic {const2, ~$1},{relative2, $2} pat zrl kills indordef, locals %ind <= $1 && %ind+%size > $1 gen clr {LOCAL, $1, 2} pat zre kills posextern gen clr {relative2, $1} pat zrf $1==4 uses FLTREG gen clrf %a yields %a pat zrf $1==8 uses DBLREG gen clrf %a yields %a pat zer $1==2 yields {const2, 0} pat zer $1==4 yields {const2,0} {const2,0} pat zer $1==6 yields {const2,0} {const2,0} {const2,0} pat zer $1==8 yields {const2,0} {const2,0} {const2,0} {const2,0} pat zer defined($1) with STACK gen move {const2,$1/2},r0 1: clr {autodec,sp} sob r0,{label, 1b} /**************************************** * Group 8 : Convert instructions * ****************************************/ pat cii with STACK gen jsr pc,{label, "cii~"} pat cfi leaving cfu pat ciu leaving cuu pat cui leaving cuu pat cfu with STACK gen jsr pc,{label, "cfi~"} pat cif with STACK gen jsr pc,{label, "cif~"} pat cuf with STACK gen jsr pc,{label, "cuf~"} pat cff with STACK gen jsr pc,{label, "cff~"} pat cuu with STACK gen jsr pc,{label, "cuu~"} pat loc loc cii $1==1 && $2==2 with src1or2 uses reusing %1,REG gen movb %1,%a yields %a pat loc loc cii $1==1 && $2==4 with src1or2 uses reusing %1,REG,REG gen movb %1,%a sxt %b yields %a %b pat loc loc cii $1==2 && $2==4 with src2 uses reusing %1,REG,REG gen move %1,%a test %a sxt %b yields %a %b pat loc loc loc cii $1>=0 && $2==2 && $3==4 leaving loc $1 loc 0 pat loc loc loc cii $1< 0 && $2==2 && $3==4 leaving loc $1 loc 0-1 pat loc loc cii $1==4 && $2==2 with src2 pat loc loc cuu $1==2 && $2==4 leaving loc 0 pat loc loc cuu $1==4 && $2==2 with src2 pat loc loc cfi leaving loc $1 loc $2 cfu pat loc loc cfu $1==4 && $2==2 with FLTREG yields {ftoint,%1} pat loc loc cfu $1==4 && $2==4 with FLTREG yields {ftolong,%1} pat loc loc cfu $1==8 && $2==2 with DBLREG yields {ftoint,%1.1} pat loc loc cfu $1==8 && $2==4 with DBLREG yields {ftolong,%1.1} pat loc loc cif $1==2 && $2==4 with src2 uses FLTREG gen movif %1,%a yields %a pat loc loc cif $1==2 && $2==8 with src2 uses DBLREG gen movif %1,%a yields %a pat loc loc cif $1==4 && $2==4 with exact long4-REGPAIR uses FLTREG gen setl. movif %1,%a seti. yields %a with STACK uses FLTREG gen setl. movif {autoinc,sp},%a seti. yields %a pat loc loc cif $1==4 && $2==8 with exact long4-REGPAIR uses DBLREG gen setl. movif %1,%a seti. yields %a with STACK uses DBLREG gen setl. movif {autoinc,sp},%a seti. yields %a pat loc loc cuf $1==2 && $2==4 with STACK uses FLTREG gen clr {autodec,sp} setl. movif {autoinc,sp},%a seti. yields %a pat loc loc cuf $1==2 && $2==8 with STACK uses DBLREG gen clr {autodec,sp} setl. movif {autoinc,sp},%a seti. yields %a pat loc loc cuf $1==4 leaving loc $1 loc $2 cif pat loc loc cff $1==4 && $2==8 with longf4 - FLTREG uses DBLREG gen movof %1,%a yields %a with FLTREG uses DBLREG gen move %1,%a.1 yields %a pat loc loc cff $1==8 && $2==4 with DBLREG yields %1.1 /**************************************** * Group 9 : Logical instructions * ****************************************/ pat and $1==2 with const2 REG gen bic {const2,~%1.num},%2 yields %2 with REG const2 gen bic {const2,~%2.num},%1 yields %1 with REG REG gen com %1 bic %1,%2 yields %2 pat and defined($1) with STACK gen move {const2,$1}, r0 jsr pc,{label, "and~"} pat ior $1==2 with REG src2 gen bis %2,%1 yields %1 with src2 REG gen bis %1,%2 yields %2 pat ior $1==8 with exact src2 src2 src2 src2 STACK gen bis %1,{regdef2,sp} bis %2,{regind2,sp,2} bis %3,{regind2,sp,4} bis %4,{regind2,sp,6} with STACK uses REG={const2,$1} gen add sp,%a bis {autoinc,sp},{autoinc,%a} bis {autoinc,sp},{autoinc,%a} bis {autoinc,sp},{autoinc,%a} bis {autoinc,sp},{autoinc,%a} pat ior defined($1) with STACK uses REG={const2,$1},REG={const2,$1/2} gen add sp,%a 1: bis {autoinc,sp},{autoinc,%a} sob %b,{label,1b} pat xor $1==2 with REG REG gen xor %1,%2 yields %2 with REG REG gen xor %2,%1 yields %1 pat xor defined($1) with STACK gen move {const2,$1},r0 jsr pc,{label, "xor~"} pat com $1==2 with REG gen com %1 yields %1 pat com defined($1) with STACK uses REG={const2,$1/2},REG gen mov sp,%b 1: com {autoinc,%b} sob %a,{label,1b} pat rol $1==2 with const2 ODDREG gen ashc {const2,%1.num-16},%2 yields %2 with REG ODDREG gen sub {const2,16},%1 ashc %1,%2 yields %2 pat rol defined($1) with STACK gen move {const2,$1},r0 jsr pc,{label, "rol~"} pat ror $1==2 with const2 ODDREG gen ashc {const2,0-%1.num},%2 yields %2 with REG ODDREG gen neg %1 ashc %1,%2 yields %2 pat ror defined($1) with STACK gen move {const2,$1},r0 jsr pc,{label, "ror~"} pat com and $1==2 && $2==2 with src2 REG gen bic %1,%2 yields %2 pat com and $1==$2 with STACK uses REG={const2,$1},REG gen mov sp,%b add %a,%b asr %a 1: bic {autoinc,sp},{autoinc,%b} sob %a,{label,1b} /******************************** * Group 10 : Set instructions * ********************************/ pat inn $1==2 with REG REG gen neg %1 ash %1,%2 bic {const2,0177776},%2 yields %2 pat loc inn $2==2 && $1==0 with REG gen bic {const2,0177776},%1 yields %1 pat loc inn $2==2 && $1==1 with REG gen asr %1 bic {const2,0177776},%1 yields %1 pat loc inn $2==2 with REG gen ash {const2,0-$1},%1 bic {const2,0177776},%1 yields %1 pat loc inn zeq $2==2 yields {const2, 1<<$1} leaving and 2 zeq $3 pat inn zeq $1==2 with src2 uses REG={const2,1} gen ash %1,%a yields %a leaving and 2 zeq $2 pat loc inn zne $2==2 yields {const2, 1<<$1} leaving and 2 zne $3 pat inn zne $1==2 with src2 uses REG={const2,1} gen ash %1,%a yields %a leaving and 2 zne $2 pat inn defined($1) with src2 STACK gen move %1,r1 move {const2,$1},r0 jsr pc,{label, "inn~"} yields r0 pat set $1==2 with REG uses REG={const2,1} gen ash %1,%a yields %a pat set defined($1) with src2 STACK gen move %1,r1 move {const2,$1},r0 jsr pc,{label, "set~"} /**************************************** * Group 11 : Array instructions * ****************************************/ pat lae aar $2==2 && rom($1,3)==1 && rom($1,1)==0 leaving adi 2 pat lae aar $2==2 && rom($1,3)==1 && rom($1,1)!=0 leaving adi 2 adp 0-rom($1,1) pat lae aar $2==2 && rom($1,3)==2 && rom($1,1)==0 with REG gen asl %1 yields %1 leaving adi 2 pat lae aar $2==2 && rom($1,3)==2 && rom($1,1)!=0 with REG gen asl %1 yields {regconst2,%1,(0-2)*rom($1,1)} leaving adi 2 pat lae aar $2==2 && rom($1,3)==4 && rom($1,1)==0 with REG gen ash {const2,2},%1 yields %1 leaving adi 2 pat lae aar $2==2 && rom($1,3)==4 && rom($1,1)!=0 with REG gen ash {const2,2},%1 yields {regconst2,%1,(0-4)*rom($1,1)} leaving adi 2 pat lae aar $2==2 && rom($1,3)==8 && rom($1,1)==0 with REG gen ash {const2,3},%1 yields %1 leaving adi 2 pat lae aar $2==2 && rom($1,3)==8 && rom($1,1)!=0 with REG gen ash {const2,3},%1 yields {regconst2,%1,(0-8)*rom($1,1)} leaving adi 2 pat lae aar $2==2 && rom($1,1)==0 with ODDREG gen mul {const2,rom($1,3)},%1 yields %1 leaving adi 2 pat lae aar $2==2 && defined(rom($1,1)) with ODDREG gen mul {const2,rom($1,3)},%1 yields {regconst2,%1,(0-rom($1,3))*rom($1,1)} leaving adi 2 pat aar $1==2 with STACK gen mov {autoinc,sp},r0 mov {autoinc,sp},r1 jsr pc,{label, "aar~"} pat lae sar defined(rom($1,3)) leaving lae $1 aar $2 sti rom($1,3) pat lae lar defined(rom($1,3)) leaving lae $1 aar $2 loi rom($1,3) pat sar $1==2 with STACK gen mov {autoinc,sp},r0 mov {autoinc,sp},r1 jsr pc,{label, "sar~"} pat lar $1==2 with STACK gen mov {autoinc,sp},r0 mov {autoinc,sp},r1 jsr pc,{label, "lar~"} /**************************************** * group 12 : Compare instructions * ****************************************/ pat cmi $1==2 with src2 REG gen sub %1,%2 yields %2 with REG src2 gen sub %2,%1 neg %1 yields %1 pat cmi $1==4 with STACK gen jsr pc,{label, "cmi4~"} yields r0 pat cmf defined($1) with STACK gen move {const2,$1},r0 jsr pc,{label, "cmf~"} yields r0 pat cmu $1==2 leaving cmp pat cmu $1==4 with STACK gen jsr pc,{label, "cmu4~"} yields r0 pat cmu defined($1) with STACK gen move {const2,$1},r0 jsr pc,{label, "cmu~"} yields r0 pat cms $1==2 leaving cmi $1 pat cms defined($1) with STACK gen move {const2,$1},r0 jsr pc,{label, "cms~"} yields r0 pat cmp with src2 src2 uses REG = {const2,0} gen cmp %1,%2 beq {label,2f} bhi {label,1f} inc %a br {label,2f} 1: dec %a 2: yields %a proc txxand with src2 REG gen test %1 bxx* {label,1f} clr %2 1: yields %2 proc txxior with src2 REG gen test %1 bxx* {label,1f} bis {const2,1},%2 1: yields %2 proc txx with src2 uses REG={const2,0} gen test %1 bxx* {label,1f} inc %a 1: yields %a pat tlt and $2==2 call txxand("blt") pat tle and $2==2 call txxand("ble") pat teq and $2==2 call txxand("beq") pat tne and $2==2 call txxand("bne") pat tgt and $2==2 call txxand("bgt") pat tge and $2==2 call txxand("bge") pat tlt ior $2==2 call txxior("bge") pat tle ior $2==2 call txxior("bgt") pat teq ior $2==2 call txxior("bne") pat tne ior $2==2 call txxior("beq") pat tgt ior $2==2 call txxior("ble") pat tge ior $2==2 call txxior("blt") pat tlt call txx("bge") pat tle call txx("bgt") pat teq call txx("bne") pat tne call txx("beq") pat tgt call txx("ble") pat tge call txx("blt") proc andtxx with src2 src2 uses REG={const2,0} gen bit %1,%2 bxx* {label,1f} inc %a 1: yields %a pat and tne $1==2 call andtxx("beq") pat and teq $1==2 call andtxx("bne") proc cmitxxand with src2 src2 REG gen cmp %2,%1 bxx* {label,1f} clr %3 1: yields %3 proc cmitxxior with src2 src2 REG gen cmp %2,%1 bxx* {label,1f} bis {const2,1},%3 1: yields %3 proc cmitxx with src2 src2 uses REG={const2,0} gen cmp %2,%1 bxx* {label,1f} inc %a 1: yields %a pat cmi tlt and $1==2 && $3==2 call cmitxxand("blt") pat cmi tle and $1==2 && $3==2 call cmitxxand("ble") pat cmi teq and $1==2 && $3==2 call cmitxxand("beq") pat cmi tne and $1==2 && $3==2 call cmitxxand("bne") pat cmi tgt and $1==2 && $3==2 call cmitxxand("bgt") pat cmi tge and $1==2 && $3==2 call cmitxxand("bge") pat cmi tlt ior $1==2 && $3==2 call cmitxxior("bge") pat cmi tle ior $1==2 && $3==2 call cmitxxior("bgt") pat cmi teq ior $1==2 && $3==2 call cmitxxior("bne") pat cmi tne ior $1==2 && $3==2 call cmitxxior("beq") pat cmi tgt ior $1==2 && $3==2 call cmitxxior("ble") pat cmi tge ior $1==2 && $3==2 call cmitxxior("blt") pat cmi tlt $1==2 call cmitxx("bge") pat cmi tle $1==2 call cmitxx("bgt") pat cmi teq $1==2 call cmitxx("bne") pat cmi tne $1==2 call cmitxx("beq") pat cmi tgt $1==2 call cmitxx("ble") pat cmi tge $1==2 call cmitxx("blt") pat loc cmi teq and $1>=0 && $1<=127 && $2==2 && $4==2 with exact src1 REG gen cmpb %1,{const2,$1} beq {label,1f} clr %2 1: yields %2 with yields {const2, $1} leaving cmi 2 teq and 2 pat loc cmi teq ior $1>=0 && $1<=127 && $2==2 && $4==2 with exact src1 REG gen cmpb %1,{const2,$1} bne {label,1f} bis {const2,1},%2 1: yields %2 with yields {const2, $1} leaving cmi 2 teq ior 2 pat loc cmi teq $1>=0 && $1<=127 && $2==2 with exact src1 uses REG={const2,0} gen cmpb %1,{const2,$1} bne {label,1f} inc %a 1: yields %a with yields {const2, $1} leaving cmi 2 teq pat loc cmi tne and $1>=0 && $1<=127 && $2==2 && $4==2 with exact src1 REG gen cmpb %1,{const2,$1} bne {label,1f} clr %2 1: yields %2 with yields {const2, $1} leaving cmi 2 tne and 2 pat loc cmi tne ior $1>=0 && $1<=127 && $2==2 && $4==2 with exact src1 REG gen cmpb %1,{const2,$1} beq {label,1f} bis {const2,1},%2 1: yields %2 with yields {const2, $1} leaving cmi 2 tne ior 2 pat loc cmi tne $1>=0 && $1<=127 && $2==2 with exact src1 uses REG={const2,0} gen cmpb %1,{const2,$1} beq {label,1f} inc %a 1: yields %a with yields {const2, $1} leaving cmi 2 tne proc cmptxx with src2 src2 uses REG={const2,0} gen cmp %2,%1 bxx* {label,1f} inc %a 1: yields %a pat cmp tlt call cmptxx("bhis") pat cmp tle call cmptxx("bhi") pat cmp teq call cmptxx("bne") pat cmp tne call cmptxx("beq") pat cmp tgt call cmptxx("blos") pat cmp tge call cmptxx("blo") proc cmf4txx with FLTREG FLTREG uses REG={const2,0} gen cmpf %2,%1 cfcc. bxx* {label,1f} inc %a 1: yields %a pat cmf tlt $1==4 call cmf4txx("bge") pat cmf tle $1==4 call cmf4txx("bgt") pat cmf teq $1==4 call cmf4txx("bne") pat cmf tne $1==4 call cmf4txx("beq") pat cmf tgt $1==4 call cmf4txx("ble") pat cmf tge $1==4 call cmf4txx("blt") proc cmf8txx with DBLREG double8 uses REG={const2,0} gen cmpf %2,%1 cfcc. bxx[1] {label,1f} inc %a 1: yields %a with double8 DBLREG uses REG={const2,0} gen cmpf %1,%2 cfcc. bxx[2] {label,1f} inc %a 1: yields %a pat cmf tlt $1==8 call cmf8txx("bge","ble") pat cmf tle $1==8 call cmf8txx("bgt","blt") pat cmf teq $1==8 call cmf8txx("bne","bne") pat cmf tne $1==8 call cmf8txx("beq","beq") pat cmf tgt $1==8 call cmf8txx("ble","bge") pat cmf tge $1==8 call cmf8txx("blt","bgt") /**************************************** * Group 13 : Branch instructions * ****************************************/ pat bra with STACK gen jbr {label, $1} proc bxx example beq with src2 src2 STACK gen cmp %2,%1 jxx* {label, $1} pat blt call bxx("jlt") pat ble call bxx("jle") pat beq call bxx("jeq") pat bne call bxx("jne") pat bgt call bxx("jgt") pat bge call bxx("jge") pat loc beq $1>=0 && $1<=127 with exact src1 STACK gen cmpb %1,{const2,$1} jeq {label, $2} with yields {const2, $1} leaving beq $2 pat loc bne $1>=0 && $1<=127 with exact src1 STACK gen cmpb %1,{const2,$1} jne {label, $2} with yields {const2, $1} leaving bne $2 proc zxx example zeq with src2 STACK gen test %1 jxx* {label, $1} pat zlt call zxx("jlt") pat zle call zxx("jle") pat zeq call zxx("jeq") pat zne call zxx("jne") pat zgt call zxx("jgt") pat zge call zxx("jge") proc cmpzxx example cmp zeq with src2 src2 STACK gen cmp %2,%1 jxx* {label, $2} pat cmp zlt call cmpzxx("jlo") pat cmp zle call cmpzxx("jlos") pat cmp zeq call cmpzxx("jeq") pat cmp zne call cmpzxx("jne") pat cmp zgt call cmpzxx("jhi") pat cmp zge call cmpzxx("jhis") proc cmf4zxx example cmf zeq with FLTREG FLTREG STACK gen cmpf %2,%1 cfcc. jxx* {label, $2} pat cmf zlt $1==4 call cmf4zxx("jlt") pat cmf zle $1==4 call cmf4zxx("jle") pat cmf zeq $1==4 call cmf4zxx("jeq") pat cmf zne $1==4 call cmf4zxx("jne") pat cmf zgt $1==4 call cmf4zxx("jgt") pat cmf zge $1==4 call cmf4zxx("jge") proc cmf8zxx example cmf zeq with DBLREG double8 STACK gen cmpf %2,%1 cfcc. jxx[1] {label, $2} with double8 DBLREG STACK gen cmpf %1,%2 cfcc. jxx[2] {label, $2} pat cmf zlt $1==8 call cmf8zxx("jlt","jgt") pat cmf zle $1==8 call cmf8zxx("jle","jge") pat cmf zeq $1==8 call cmf8zxx("jeq","jeq") pat cmf zne $1==8 call cmf8zxx("jne","jne") pat cmf zgt $1==8 call cmf8zxx("jgt","jlt") pat cmf zge $1==8 call cmf8zxx("jge","jle") proc andzen example and zeq with src2 src2 STACK gen bit %1,%2 jxx* {label, $2} pat and zeq $1==2 call andzen("jeq") pat and zne $1==2 call andzen("jne") /************************************************ * group 14 : Procedure call instructions * ************************************************/ pat cal with STACK gen jsr pc,{label, $1} pat cai with REG STACK gen jsr pc,{regdef2,%1} pat lfr $1==2 yields r0 pat lfr $1==4 yields r1 r0 pat lfr $1==8 yields {relative8,"retar"} pat lfr with STACK gen move {const2,$1},r0 jsr pc,{label, "lfr~"} pat lfr ret $1==$2 leaving ret 0 pat ret $1==0 with STACK gen mov lb,sp mov {autoinc, sp},lb rts pc pat ret $1==2 with src2 STACK gen move %1,r0 mov lb,sp mov {autoinc, sp},lb rts pc pat ret $1==4 with STACK gen mov {autoinc,sp},r0 mov {autoinc,sp},r1 mov lb,sp mov {autoinc, sp},lb rts pc pat ret $1==8 yields {addr_external, "retar"} leaving sti 8 ret 0 pat ret with STACK gen move {const2,$1},r0 jmp {label,"ret~"} /************************************************ * Group 15 : Miscellaneous instructions * ************************************************/ pat asp $1==2 with STACK gen tst {autoinc,sp} pat asp $1==4 with STACK gen cmp {autoinc,sp},{autoinc,sp} pat asp $1==0-2 with STACK gen tst {autodec,sp} pat asp with STACK gen add {const2,$1},sp pat ass $1==2 with STACK gen add {autoinc,sp},sp pat blm $1==4 with REG REG gen mov {autoinc,%2},{autoinc,%1} mov {regdef2,%2},{regdef2,%1} pat blm $1==6 with REG REG gen mov {autoinc,%2},{autoinc,%1} mov {autoinc,%2},{autoinc,%1} mov {regdef2,%2},{regdef2,%1} pat blm $1==8 with REG REG gen mov {autoinc,%2},{autoinc,%1} mov {autoinc,%2},{autoinc,%1} mov {autoinc,%2},{autoinc,%1} mov {regdef2,%2},{regdef2,%1} pat blm with REG REG uses REG={const2,$1/2} gen 1: mov {autoinc,%2},{autoinc,%1} sob %a,{label,1b} pat lae csa $2==2 with src2 STACK gen move %1,r1 move {addr_external,$1},r0 jmp {label, "csa~"} pat csa $1==2 with STACK gen mov {autoinc,sp},r0 mov {autoinc,sp},r1 jmp {label, "csa~"} pat lae csb $2==2 with src2 STACK gen move %1,r1 move {addr_external,$1},r0 jmp {label, "csb~"} pat csb $1==2 with STACK gen mov {autoinc,sp},r0 mov {autoinc,sp},r1 jmp {label, "csb~"} pat dup $1==2 with REG yields %1 %1 pat dup $1==4 with exact long4 yields %1 %1 with src2 src2 yields %2 %1 %2 %1 pat dup $1==8 with exact long8 yields %1 %1 with STACK gen move {const2, $1}, r0 jsr pc,{label, "dup~"} pat dup with STACK gen move {const2, $1}, r0 jsr pc,{label, "dup~"} pat dus $1==2 with src2 STACK gen move %1,r0 jsr pc,{label, "dup~"} pat gto with STACK gen mov {addr_external, $1},{autodec,sp} jmp {label, "gto~"} pat fil gen mov {addr_external, $1},{relative2, "hol0"+4} pat lim yields { relative2, "trpim~"} pat lin gen mov {const2,$1},{relative2, "hol0"} pat lni gen inc {relative2, "hol0"} pat lor $1==0 yields lb pat lor $1==1 with STACK uses REG gen mov sp,%a yields %a pat lor $1==2 yields {relative2,"reghp~"} pat mon with STACK gen jsr pc,{label, "mon~"} pat nop with STACK gen jsr pc,{label, "nop~"} pat rck $1==2 with src2 pat rtt leaving ret 0 pat sig with src2 uses REG gen move {relative2,"trppc~"},%a mov %1,{relative2,"trppc~"} yields %a pat sim with STACK gen jsr pc,{label, "sim~"} pat str $1==0 with src2 gen mov %1,lb pat str $1==1 with src2 STACK gen mov %1,sp pat str $1==2 with STACK gen jsr pc,{label, "strhp~"} pat trp with STACK gen jsr pc,{label, "trp~"} pat exg $1==2 with src2 src2 yields %1 %2 pat exg defined($1) with STACK gen move {const2,$1},r0 jsr pc,{label, "exg~"} pat lol lal sti $1==$2 && $3==1 /* throw away funny C-proc-prolog */ pat los gen jmp {label, illins} pat sts gen jmp {label, illins} pat inn gen jmp {label, illins} pat set gen jmp {label, illins}