xref: /csrg-svn/old/pcc/c2.vax/c21.c (revision 1496)
1*1496Sbill static	char sccsid[] = "@(#)c21.c 4.1 10/17/80";
2*1496Sbill /* char C21[] = {"@(#)c21.c 1.82 - 81 ??/??/?? ??:??:?? JFR"}; /* sccs ident */
3*1496Sbill 
4*1496Sbill /*
5*1496Sbill  * C object code improver-- second part
6*1496Sbill  */
7*1496Sbill 
8*1496Sbill #include "c2.h"
9*1496Sbill #include <stdio.h>
10*1496Sbill #include <ctype.h>
11*1496Sbill 
12*1496Sbill #define NUSE 6
13*1496Sbill int ioflag;
14*1496Sbill int biti[NUSE] = {1,2,4,8,16,32};
15*1496Sbill int bitsize[4] = {0,8,16,32}; /* index by type codes */
16*1496Sbill int pos,siz; long f; /* for bit field communication */
17*1496Sbill struct node *uses[NUSE]; /* for backwards flow analysis */
18*1496Sbill char *lastrand; /* last operand of instruction */
19*1496Sbill struct node *bflow();
20*1496Sbill struct node *bicopt();
21*1496Sbill char *findcon();
22*1496Sbill 
23*1496Sbill redun3(p,split) register struct node *p; int split; {
24*1496Sbill /* check for 3 addr instr which should be 2 addr */
25*1496Sbill 	if (OP3==((p->subop>>4)&0xF)) {
26*1496Sbill 		if (split) splitrand(p);
27*1496Sbill 		if (equstr(regs[RT1],regs[RT3])
28*1496Sbill 		  && (p->op==ADD || p->op==MUL || p->op==BIS || p->op==XOR)) {
29*1496Sbill 			register char *t=regs[RT1]; regs[RT1]=regs[RT2]; regs[RT2]=t;
30*1496Sbill 		}
31*1496Sbill 		if (equstr(regs[RT2],regs[RT3])) {
32*1496Sbill 			p->subop=(p->subop&0xF)|(OP2<<4); p->pop=0;
33*1496Sbill 			lastrand=regs[RT2]; *regs[RT3]=0; return(1);
34*1496Sbill 		}
35*1496Sbill 	} return(0);
36*1496Sbill }
37*1496Sbill 
38*1496Sbill bmove() {
39*1496Sbill 	register struct node *p, *lastp; register char *cp1,*cp2; register int r;
40*1496Sbill 	refcount();
41*1496Sbill 	for (p=lastp= &first; 0!=(p=p->forw); lastp=p);
42*1496Sbill 	clearreg(); clearuse();
43*1496Sbill 	for (p=lastp; p!= &first; p=p->back) {
44*1496Sbill 	if (debug) {
45*1496Sbill 		printf("Uses:\n");
46*1496Sbill 		for (r=NUSE;--r>=0;) if (uses[r])
47*1496Sbill 			printf("%d: %s\n",r,uses[r]->code? uses[r]->code:"");
48*1496Sbill 		printf("-\n");
49*1496Sbill 	}
50*1496Sbill 	r=(p->subop>>4)&0xF;
51*1496Sbill 	if (OP2==r && (cp1=p->code, *cp1++)=='$' && *cp1++=='0' && *cp1++==',' &&
52*1496Sbill 			!source(cp1)) {/* a no-op unless MUL or DIV */
53*1496Sbill 		if (p->op==MUL) {p->op=MOV; p->subop&=0xF; p->pop=0;}
54*1496Sbill 		else if (p->op==DIV) fprintf(stderr,"c2: zero divide\n");
55*1496Sbill 		else {delnode(p); redunm++; continue;}
56*1496Sbill 	}
57*1496Sbill 	if (OP3==r && 0!=redun3(p,1)) {newcode(p); redunm++;}
58*1496Sbill 	switch (p->op) {
59*1496Sbill 	case LABEL: case DLABEL:
60*1496Sbill 		for (r=NUSE; --r>=0;)
61*1496Sbill 			if (uses[r]) p->ref=(struct node *) (((int)p->ref)|biti[r]);
62*1496Sbill 		break;
63*1496Sbill 	case CALLS:
64*1496Sbill 		clearuse(); goto std;
65*1496Sbill 	case 0:
66*1496Sbill 		clearuse(); break;
67*1496Sbill 	case SUB:
68*1496Sbill 		if ((p->subop&0xF)!=LONG) goto std; cp1=p->code;
69*1496Sbill 		if (*cp1++!='$') goto std; splitrand(p);
70*1496Sbill 		if (equstr(regs[RT2],"fp") && !indexa(regs[RT1])) {/* address comp. */
71*1496Sbill 			char buf[50]; cp2=buf; *cp2++='-';
72*1496Sbill 			cp1=regs[RT1]+1; while (*cp2++= *cp1++); --cp2;
73*1496Sbill 			cp1="(fp),"; while (*cp2++= *cp1++); --cp2;
74*1496Sbill 			cp1=regs[RT3]; while (*cp2++= *cp1++);
75*1496Sbill 			p->code=copy(buf); p->combop=T(MOVA,LONG); p->pop=0;
76*1496Sbill 		} else if (*cp1++=='-' && 0<=(r=getnum(cp1))) {
77*1496Sbill 			p->op=ADD; p->pop=0; *--cp1='$'; p->code=cp1;
78*1496Sbill 		} goto std;
79*1496Sbill 	case ADD:
80*1496Sbill 		if ((p->subop&0xF)!=LONG) goto std; cp1=p->code;
81*1496Sbill 		if (*cp1++!='$') goto std; splitrand(p);
82*1496Sbill 		if (isstatic(cp1) && (r=isreg(regs[RT2]))>=0 && r<NUSE && uses[r]==p->forw)
83*1496Sbill 		{
84*1496Sbill 			/* address comp:
85*1496Sbill 			**	addl2	$_foo,r0  \	movab	_foo[r0],bar
86*1496Sbill 			**	movl	r0,bar	  /
87*1496Sbill 			*/
88*1496Sbill 			register struct	node	*pnext = p->forw;
89*1496Sbill 			char	buf[50];
90*1496Sbill 
91*1496Sbill 			if (pnext->op == MOV && pnext->subop == LONG)
92*1496Sbill 			{
93*1496Sbill 				cp1 = &regs[RT1][1]; cp2 = &buf[0];
94*1496Sbill 				while (*cp2++ = *cp1++) ; cp2--;
95*1496Sbill 				splitrand(pnext);
96*1496Sbill 				if (r == isreg(regs[RT1]))
97*1496Sbill 				{
98*1496Sbill 					delnode(p); p = pnext;
99*1496Sbill 					p->op = MOVA; p->subop = BYTE;
100*1496Sbill 					p->pop = 0;
101*1496Sbill 					cp1 = regs[RT1]; *cp2++ = '[';
102*1496Sbill 					while (*cp2++ = *cp1++) ; cp2--;
103*1496Sbill 					*cp2++ = ']'; *cp2++ = ',';
104*1496Sbill 					cp1 = regs[RT2];
105*1496Sbill 					while (*cp2++ = *cp1++) ;
106*1496Sbill 					p->code = copy(buf);
107*1496Sbill 				}
108*1496Sbill 			}
109*1496Sbill 		}
110*1496Sbill 		else
111*1496Sbill 		if (equstr(regs[RT2],"fp") && !indexa(regs[RT1])) {/* address comp. */
112*1496Sbill 			cp2=cp1-1; cp1=regs[RT1]+1; while (*cp2++= *cp1++); --cp2;
113*1496Sbill 			cp1="(fp)"; while (*cp2++= *cp1++); *--cp2=',';
114*1496Sbill 			p->combop=T(MOVA,LONG); p->pop=0;
115*1496Sbill 		} else if (*cp1++=='-' && 0<=(r=getnum(cp1))) {
116*1496Sbill 			p->op=SUB; p->pop=0; *--cp1='$'; p->code=cp1;
117*1496Sbill 		}
118*1496Sbill 		/* fall thru ... */
119*1496Sbill 	case CASE:
120*1496Sbill 	default: std:
121*1496Sbill 		p=bflow(p); break;
122*1496Sbill 	case MUL:
123*1496Sbill 	{
124*1496Sbill 		/*
125*1496Sbill 		** Change multiplication by constant powers of 2 to
126*1496Sbill 		**	shifts.
127*1496Sbill 		*/
128*1496Sbill 		splitrand(p);
129*1496Sbill 		if (regs[RT1][0] != '$' || regs[RT1][1] == '-') goto std;
130*1496Sbill 		if ((r = ispow2(getnum(&regs[RT1][1]))) < 0) goto std;
131*1496Sbill 		switch (r)
132*1496Sbill 		{
133*1496Sbill 		case 0:		/* mull3 $1,x,y */
134*1496Sbill 			if (p->subop == U(LONG,OP3))
135*1496Sbill 			{
136*1496Sbill 				if (equstr(regs[RT2], regs[RT3]))
137*1496Sbill 				{
138*1496Sbill 					delnode(p); p = p->forw;
139*1496Sbill 				}
140*1496Sbill 				else
141*1496Sbill 				{
142*1496Sbill 					p->op = MOV; p->subop = LONG;
143*1496Sbill 					p->pop = 0; newcode(p); nchange++;
144*1496Sbill 				}
145*1496Sbill 			}
146*1496Sbill 			else
147*1496Sbill 			if (p->subop == U(LONG,OP2))
148*1496Sbill 			{
149*1496Sbill 				delnode(p); p = p->forw;
150*1496Sbill 			}
151*1496Sbill 			goto std;
152*1496Sbill 
153*1496Sbill 		case 1:		/* mull2 $2,x */
154*1496Sbill 			if (p->subop == U(LONG, OP2) && !source(regs[RT2]))
155*1496Sbill 			{
156*1496Sbill 				strcpy(regs[RT1], regs[RT2]);
157*1496Sbill 				p->op = ADD; p->pop = 0; newcode(p); nchange++;
158*1496Sbill 			}
159*1496Sbill 			goto std;
160*1496Sbill 		}
161*1496Sbill 		if(p->subop==U(LONG,OP3)||(p->subop==U(LONG,OP2)&&!source(regs[RT2])))
162*1496Sbill 		{
163*1496Sbill 			if (p->subop == U(LONG,OP2))
164*1496Sbill 				strcpy(regs[RT3], regs[RT2]);
165*1496Sbill 			sprintf(regs[RT1], "$%d", r);
166*1496Sbill 			p->op = ASH; p->subop = LONG;
167*1496Sbill 			p->pop = 0; newcode(p); nchange++;
168*1496Sbill 		}
169*1496Sbill 		goto std;
170*1496Sbill 	}
171*1496Sbill 	case ASH:
172*1496Sbill 	{
173*1496Sbill 		/* address comp:
174*1496Sbill 		**	ashl	$1,bar,r0  \	movl	bar,r0
175*1496Sbill 		**	movab	_foo[r0]   /	movaw	_foo[r0]
176*1496Sbill 		**
177*1496Sbill 		**	ashl	$2,r0,r0   \	moval	_foo[r0]
178*1496Sbill 		**	movab	_foo[r0]   /
179*1496Sbill 		*/
180*1496Sbill 		register struct	node	*pf;
181*1496Sbill 		register int	shfrom, shto;
182*1496Sbill 		long	shcnt;
183*1496Sbill 		char	*regfrom;
184*1496Sbill 
185*1496Sbill 		splitrand(p);
186*1496Sbill 		if (regs[RT1][0] != '$') goto std;
187*1496Sbill 		if ((shcnt = getnum(&regs[RT1][1])) < 1 || shcnt > 3) goto std;
188*1496Sbill 		if ((shfrom = isreg(regs[RT2])) >= 0)
189*1496Sbill 			regfrom = copy(regs[RT2],"]");
190*1496Sbill 		if ((shto = isreg(regs[RT3])) >= 0 && shto<NUSE)
191*1496Sbill 		{
192*1496Sbill 			int	regnum;
193*1496Sbill 
194*1496Sbill 			if (uses[shto] != (pf = p->forw)) goto ashadd;
195*1496Sbill 			if (pf->op != MOVA && pf->op != PUSHA) goto ashadd;
196*1496Sbill 			if (pf->subop != BYTE) goto ashadd;
197*1496Sbill 			splitrand(pf);
198*1496Sbill 			if (!indexa(regs[RT1])) goto std;
199*1496Sbill 			cp2 = regs[RT1];
200*1496Sbill 			if(!isstatic(cp2)) goto std;
201*1496Sbill 			while (*cp2++ != '[') ;
202*1496Sbill 			if (*cp2++ != 'r' || !isdigit(*cp2)) goto std;
203*1496Sbill 			regnum = *cp2++ - '0';
204*1496Sbill 			if (isdigit(*cp2))
205*1496Sbill 			{
206*1496Sbill 				if (cp2[1] != ']') goto std;
207*1496Sbill 				regnum *= 10; regnum += *cp2 - '0';
208*1496Sbill 			}
209*1496Sbill 			if (regnum != shto) goto std;
210*1496Sbill 			if (shfrom >= 0)	/* ashl $N,r*,r0 */
211*1496Sbill 			{
212*1496Sbill 				delnode(p);
213*1496Sbill 				if (shfrom != shto)
214*1496Sbill 				{
215*1496Sbill 					uses[shto] = NULL; splitrand(pf);
216*1496Sbill 					cp2=regs[RT1]; while (*cp2++!='[');
217*1496Sbill 					cp1=regfrom; while (*cp2++= *cp1++);
218*1496Sbill 					newcode(pf);
219*1496Sbill 				}
220*1496Sbill 			}
221*1496Sbill 			else
222*1496Sbill 			{
223*1496Sbill 				p->op = MOV; splitrand(p);
224*1496Sbill 				strcpy(regs[RT1], regs[RT2]);
225*1496Sbill 				strcpy(regs[RT2], regs[RT3]);
226*1496Sbill 				regs[RT3][0] = '\0';
227*1496Sbill 				p->pop = 0; newcode(p);
228*1496Sbill 			}
229*1496Sbill 			switch (shcnt)
230*1496Sbill 			{
231*1496Sbill 			case 1:	pf->subop = WORD; break;
232*1496Sbill 			case 2:	pf->subop = LONG; break;
233*1496Sbill 			case 3:	pf->subop = QUAD; break;
234*1496Sbill 			}
235*1496Sbill 			redunm++; nsaddr++; nchange++;
236*1496Sbill 		}
237*1496Sbill 		goto std;
238*1496Sbill ashadd:
239*1496Sbill 		/* at this point, RT2 and RT3 are guaranteed to be simple regs*/
240*1496Sbill 		if (shcnt == 1 && equstr(regs[RT2], regs[RT3]))
241*1496Sbill 		{
242*1496Sbill 			/*
243*1496Sbill 			** quickie:
244*1496Sbill 			**	ashl	$1,A,A	>	addl2	A,A
245*1496Sbill 			*/
246*1496Sbill 			p->op = ADD; p->subop = U(LONG,OP2); p->pop = 0;
247*1496Sbill 			strcpy(regs[RT1], regs[RT2]); regs[RT3][0] = '\0';
248*1496Sbill 			newcode(p); nchange++;
249*1496Sbill 		}
250*1496Sbill 		goto std;
251*1496Sbill 	}
252*1496Sbill 
253*1496Sbill 	case EXTV:
254*1496Sbill 	case EXTZV:
255*1496Sbill 	{
256*1496Sbill 		/* bit tests:
257*1496Sbill 		**	extv	A,$1,B,rC  \
258*1496Sbill 		**	tstl	rC	    >	jbc	A,B,D
259*1496Sbill 		**	jeql	D	   /
260*1496Sbill 		**
261*1496Sbill 		** also byte- and word-size fields:
262*1496Sbill 		**	extv	$n*8,$8,A,B	>	cvtbl	n+A,B
263*1496Sbill 		**	extv	$n*16,$16,A,B	>	cvtwl	n+A,B
264*1496Sbill 		**	extzv	$n*8,$8,A,B	>	movzbl	n+A,B
265*1496Sbill 		**	extzv	$n*16,$16,A,B	>	movzwl	n+A,B
266*1496Sbill 		*/
267*1496Sbill 		register struct	node	*pf;	/* forward node */
268*1496Sbill 		register struct	node	*pn;	/* next node (after pf) */
269*1496Sbill 		int	flen;			/* field length */
270*1496Sbill 
271*1496Sbill 		splitrand(p);
272*1496Sbill 		if (regs[RT2][0] != '$') goto std;
273*1496Sbill 		if ((flen = getnum(&regs[RT2][1])) < 0) goto std;
274*1496Sbill 		if (flen == 1)
275*1496Sbill 		{
276*1496Sbill 			register int	extreg;		/* reg extracted to */
277*1496Sbill 
278*1496Sbill 			extreg = isreg(regs[RT4]);
279*1496Sbill 			if (extreg < 0 || extreg >= NUSE) goto std;
280*1496Sbill 			if ((pf = p->forw)->op != TST) goto std;
281*1496Sbill 			if (uses[extreg] && uses[extreg] != pf) goto std;
282*1496Sbill 			splitrand(pf);
283*1496Sbill 			if (extreg != isreg(regs[RT1])) goto std;
284*1496Sbill 			if ((pn = pf->forw)->op != CBR) goto std;
285*1496Sbill 			if (pn->subop != JEQ && pn->subop != JNE) goto std;
286*1496Sbill 			delnode(p); delnode(pf);
287*1496Sbill 			pn->subop = (pn->subop == JEQ) ? JBC : JBS;
288*1496Sbill 			for(cp2=p->code; *cp2++!=',';);
289*1496Sbill 			for(cp1=cp2;     *cp1++!=',';);
290*1496Sbill 			while (*cp1!=',') *cp2++= *cp1++; *cp2='\0';
291*1496Sbill 			pn->code = p->code; pn->pop = NULL;
292*1496Sbill 			uses[extreg] = NULL;
293*1496Sbill 		}
294*1496Sbill 		else
295*1496Sbill 		if (flen == 8 || flen == 16)
296*1496Sbill 		{
297*1496Sbill 			register int	boff;	/* bit offset */
298*1496Sbill 			register int	coff;	/* chunk (byte or word) offset*/
299*1496Sbill 
300*1496Sbill 			if (regs[RT1][0] != '$') goto std;
301*1496Sbill 			if ((boff = getnum(&regs[RT1][1])) < 0) goto std;
302*1496Sbill 			coff = boff / flen;
303*1496Sbill 			if (coff && (isreg(regs[RT3]) >= 0)) goto std;
304*1496Sbill 			if (boff < 0 || (boff % flen) != 0) goto std;
305*1496Sbill 			p->op = (p->op == EXTV) ? CVT : MOVZ;
306*1496Sbill 			p->subop = U((flen == 8 ? BYTE : WORD), LONG);
307*1496Sbill 			if (coff == 0)
308*1496Sbill 				strcpy(regs[RT1], regs[RT3]);
309*1496Sbill 			else
310*1496Sbill 				sprintf(regs[RT1], "%d%s%s", coff, regs[RT3][0]=='(' ? "":"+",
311*1496Sbill 					regs[RT3]);
312*1496Sbill 			strcpy(regs[RT2], regs[RT4]);
313*1496Sbill 			regs[RT3][0] = '\0'; regs[RT4][0] = '\0';
314*1496Sbill 			p->pop = 0; newcode(p);
315*1496Sbill 		}
316*1496Sbill 		nchange++;
317*1496Sbill 		goto std;
318*1496Sbill 	}
319*1496Sbill 
320*1496Sbill 	case CMP:
321*1496Sbill 	{
322*1496Sbill 		/* comparison to -63 to -1:
323*1496Sbill 		**	cmpl	r0,$-1	>	incl	r0
324*1496Sbill 		**	jeql	...
325*1496Sbill 		**
326*1496Sbill 		**	cmpl	r0,$-63	>	addl2	$63,r0
327*1496Sbill 		**	jeql	...
328*1496Sbill 		*/
329*1496Sbill 		register int	num;
330*1496Sbill 		register int	reg;
331*1496Sbill 		register struct	node	*regp = p->back;
332*1496Sbill 
333*1496Sbill 		if (p->forw->op != CBR) goto std;
334*1496Sbill 		if (p->forw->subop != JEQ && p->forw->subop != JNE) goto std;
335*1496Sbill 		splitrand(p);
336*1496Sbill 		if (strncmp(regs[RT2], "$-", 2) != 0) goto std;
337*1496Sbill 		reg = r = isreg(regs[RT1]);
338*1496Sbill 		if (r < 0) goto std;
339*1496Sbill 		if (r < NUSE && uses[r] != 0) goto std;
340*1496Sbill 		if (r >= NUSE && regp->op == MOV && p->subop == regp->subop)
341*1496Sbill 		{
342*1496Sbill 			if (*regp->code != 'r') goto std;
343*1496Sbill 			reg = regp->code[1] - '0';
344*1496Sbill 			if (isdigit(regp->code[2]) || reg >= NUSE || uses[reg])
345*1496Sbill 				goto std;
346*1496Sbill 		}
347*1496Sbill 		if (r >= NUSE) goto std;
348*1496Sbill 		if (reg != r)
349*1496Sbill 			sprintf(regs[RT1], "r%d", reg);
350*1496Sbill 		if ((num = getnum(&regs[RT2][2])) <= 0 || num > 63) goto std;
351*1496Sbill 		if (num == 1)
352*1496Sbill 		{
353*1496Sbill 			p->op = INC; regs[RT2][0] = '\0';
354*1496Sbill 		}
355*1496Sbill 		else
356*1496Sbill 		{
357*1496Sbill 			register char	*t;
358*1496Sbill 
359*1496Sbill 			t=regs[RT1];regs[RT1]=regs[RT2];regs[RT2]=t;
360*1496Sbill 			p->op = ADD; p->subop = U(p->subop, OP2);
361*1496Sbill 			for (t = &regs[RT1][2]; t[-1] = *t; t++) ;
362*1496Sbill 		}
363*1496Sbill 		p->pop = 0; newcode(p);
364*1496Sbill 		nchange++;
365*1496Sbill 		goto std;
366*1496Sbill 	}
367*1496Sbill 
368*1496Sbill 	case JSB:
369*1496Sbill 		if (equstr(p->code,"mcount")) {uses[0]=p; regs[0][0]= -1;}
370*1496Sbill 		goto std;
371*1496Sbill 	case JBR: case JMP:
372*1496Sbill 		clearuse();
373*1496Sbill 		if (p->subop==RET || p->subop==RSB) {uses[0]=p; regs[0][0]= -1; break;}
374*1496Sbill 		if (p->ref==0) goto std;	/* jmp (r0) */
375*1496Sbill 		/* fall through */
376*1496Sbill 	case CBR:
377*1496Sbill 		if (p->ref->ref!=0) for (r=NUSE;--r>=0;)
378*1496Sbill 			if (biti[r] & (int)p->ref->ref) {uses[r]=p; regs[r][0]= -1;}
379*1496Sbill 	case EROU: case JSW:
380*1496Sbill 	case TEXT: case DATA: case BSS: case ALIGN: case WGEN: case END: ;
381*1496Sbill 	}
382*1496Sbill 	}
383*1496Sbill 	for (p= &first; p!=0; p=p->forw)
384*1496Sbill 		if (p->op==LABEL || p->op==DLABEL) p->ref=0;	/* erase our tracks */
385*1496Sbill }
386*1496Sbill 
387*1496Sbill rmove()
388*1496Sbill {
389*1496Sbill 	register struct node *p, *lastp;
390*1496Sbill 	register int r;
391*1496Sbill 	int r1;
392*1496Sbill 
393*1496Sbill 	clearreg();
394*1496Sbill 	for (p=first.forw; p!=0; p = p->forw) {
395*1496Sbill 	lastp=p;
396*1496Sbill 	if (debug) {
397*1496Sbill 		printf("Regs:\n");
398*1496Sbill 		for (r=0; r<NREG; r++)
399*1496Sbill 			if (regs[r][0]) {
400*1496Sbill 				r1=regs[r][0];
401*1496Sbill 				printf("%d: %d%d %s\n", r, r1&0xF, r1>>4, regs[r]+1);
402*1496Sbill 			}
403*1496Sbill 		printf("-\n");
404*1496Sbill 	}
405*1496Sbill 	switch (p->op) {
406*1496Sbill 
407*1496Sbill 	case CVT:
408*1496Sbill 		splitrand(p); goto mov;
409*1496Sbill 
410*1496Sbill 	case MOV:
411*1496Sbill 		splitrand(p);
412*1496Sbill 		if ((r = findrand(regs[RT1],p->subop)) >= 0) {
413*1496Sbill 			if (r == isreg(regs[RT2]) && p->forw->op!=CBR) {
414*1496Sbill 				delnode(p); redunm++; break;
415*1496Sbill 			}
416*1496Sbill 		}
417*1496Sbill mov:
418*1496Sbill 		repladdr(p);
419*1496Sbill 		r = isreg(regs[RT1]);
420*1496Sbill 		r1 = isreg(regs[RT2]);
421*1496Sbill 		dest(regs[RT2],p->subop);
422*1496Sbill  		if (r>=0) {
423*1496Sbill  			if (r1>=0) savereg(r1, regs[r]+1, p->subop);
424*1496Sbill  			else if (p->op!=CVT) savereg(r, regs[RT2], p->subop);
425*1496Sbill  		} else if (r1>=0) savereg(r1, regs[RT1], p->subop);
426*1496Sbill  		else if (p->op!=CVT) setcon(regs[RT1], regs[RT2], p->subop);
427*1496Sbill 		break;
428*1496Sbill 
429*1496Sbill /* .rx,.wx */
430*1496Sbill 	case MFPR:
431*1496Sbill 	case COM:
432*1496Sbill 	case NEG:
433*1496Sbill /* .rx,.wx or .rx,.rx,.wx */
434*1496Sbill 	case ADD:
435*1496Sbill 	case SUB:
436*1496Sbill 	case BIC:
437*1496Sbill 	case BIS:
438*1496Sbill 	case XOR:
439*1496Sbill 	case MUL:
440*1496Sbill 	case DIV:
441*1496Sbill 	case ASH:
442*1496Sbill 	case MOVZ:
443*1496Sbill /* .rx,.rx,.rx,.wx */
444*1496Sbill 	case EXTV:
445*1496Sbill 	case EXTZV:
446*1496Sbill 	case INSV:
447*1496Sbill 		splitrand(p);
448*1496Sbill 		repladdr(p);
449*1496Sbill 		dest(lastrand,p->subop);
450*1496Sbill 		if (p->op==INSV) ccloc[0]=0;
451*1496Sbill 		break;
452*1496Sbill 
453*1496Sbill /* .mx or .wx */
454*1496Sbill 	case CLR:
455*1496Sbill 	case INC:
456*1496Sbill 	case DEC:
457*1496Sbill 		splitrand(p);
458*1496Sbill 		dest(lastrand,p->subop);
459*1496Sbill 		if (p->op==CLR)
460*1496Sbill 			if ((r = isreg(regs[RT1])) >= 0)
461*1496Sbill 				savereg(r, "$0", p->subop);
462*1496Sbill 			else
463*1496Sbill 				setcon("$0", regs[RT1], p->subop);
464*1496Sbill 		break;
465*1496Sbill 
466*1496Sbill /* .rx */
467*1496Sbill 	case TST:
468*1496Sbill 	case PUSH:
469*1496Sbill 		splitrand(p);
470*1496Sbill 		lastrand=regs[RT1+1]; /* fool repladdr into doing 1 operand */
471*1496Sbill 		repladdr(p);
472*1496Sbill 		if (p->op==TST && equstr(lastrand=regs[RT1], ccloc+1)
473*1496Sbill 		  && ((0xf&(ccloc[0]>>4))==p->subop || equtype(ccloc[0],p->subop))
474*1496Sbill 		  &&!source(lastrand)) {
475*1496Sbill 			delnode(p); p = p->back; nrtst++; nchange++;
476*1496Sbill 		}
477*1496Sbill 		setcc(lastrand,p->subop);
478*1496Sbill 		break;
479*1496Sbill 
480*1496Sbill /* .rx,.rx,.rx */
481*1496Sbill 	case PROBER:
482*1496Sbill 	case PROBEW:
483*1496Sbill 	case CASE:
484*1496Sbill 	case MOVC3:
485*1496Sbill /* .rx,.rx */
486*1496Sbill 	case MTPR:
487*1496Sbill 	case CALLS:
488*1496Sbill 	case CMP:
489*1496Sbill 	case BIT:
490*1496Sbill 		splitrand(p);
491*1496Sbill 		/* fool repladdr into doing right number of operands */
492*1496Sbill 		if (p->op==CASE || p->op==MOVC3 || p->op==PROBER || p->op==PROBEW)
493*1496Sbill 			lastrand=regs[RT4];
494*1496Sbill 		else lastrand=regs[RT3];
495*1496Sbill 		repladdr(p);
496*1496Sbill 		if (p->op==CALLS || p->op==MOVC3) clearreg();
497*1496Sbill 		if (p->op==BIT) bitopt(p);
498*1496Sbill 		ccloc[0]=0; break;
499*1496Sbill 
500*1496Sbill 	case CBR:
501*1496Sbill 		if (p->subop>=JBC) {
502*1496Sbill 			splitrand(p);
503*1496Sbill 			if (p->subop<JBCC) lastrand=regs[RT3]; /* 2 operands can be optimized */
504*1496Sbill 			else lastrand=regs[RT2]; /* .mb destinations lose */
505*1496Sbill 			repladdr(p);
506*1496Sbill 		}
507*1496Sbill 		ccloc[0] = 0;
508*1496Sbill 		break;
509*1496Sbill 
510*1496Sbill 	case JBR:
511*1496Sbill 		redunbr(p);
512*1496Sbill 
513*1496Sbill /* .wx,.bb */
514*1496Sbill 	case SOB:
515*1496Sbill 
516*1496Sbill 	default:
517*1496Sbill 		clearreg();
518*1496Sbill 	}
519*1496Sbill 	}
520*1496Sbill }
521*1496Sbill 
522*1496Sbill char *
523*1496Sbill byondrd(p) register struct node *p; {
524*1496Sbill /* return pointer to register which is "beyond last read/modify operand" */
525*1496Sbill 	if (OP2==(p->subop>>4)) return(regs[RT3]);
526*1496Sbill 	switch (p->op) {
527*1496Sbill 		case MFPR:
528*1496Sbill 		case JSB:
529*1496Sbill 		case PUSHA:
530*1496Sbill 		case TST: case INC: case DEC: case PUSH:	return(regs[RT2]);
531*1496Sbill 		case MTPR:
532*1496Sbill 		case BIT: case CMP: case CALLS:				return(regs[RT3]);
533*1496Sbill 		case PROBER: case PROBEW:
534*1496Sbill 		case CASE: case MOVC3:						return(regs[RT4]);
535*1496Sbill 	}
536*1496Sbill 	return(lastrand);
537*1496Sbill }
538*1496Sbill 
539*1496Sbill struct node *
540*1496Sbill bflow(p)
541*1496Sbill register struct node *p;
542*1496Sbill {
543*1496Sbill 	register char *cp1,*cp2,**preg; register int r;
544*1496Sbill 	int flow= -1;
545*1496Sbill 	struct node *olduse=0;
546*1496Sbill 	splitrand(p);
547*1496Sbill 	if (p->op!=PUSH && p->subop && 0<=(r=isreg(lastrand)) && r<NUSE && uses[r]==p->forw) {
548*1496Sbill 	if (equtype(p->subop,regs[r][0])
549*1496Sbill 	|| ((p->op==CVT || p->op==MOVZ)
550*1496Sbill 			 && 0xf&regs[r][0] && compat(0xf&(p->subop>>4),regs[r][0]))) {
551*1496Sbill 		register int r2;
552*1496Sbill 		if (regs[r][1]!=0) {/* send directly to destination */
553*1496Sbill 			if (p->op==INC || p->op==DEC) {
554*1496Sbill 				if (p->op==DEC) p->op=SUB; else p->op=ADD;
555*1496Sbill 				p->subop=(OP2<<4)+(p->subop&0xF); /* use 2 now, convert to 3 later */
556*1496Sbill 				p->pop=0;
557*1496Sbill 				cp1=lastrand; cp2=regs[RT2]; while (*cp2++= *cp1++); /* copy reg */
558*1496Sbill 				cp1=lastrand; *cp1++='$'; *cp1++='1'; *cp1=0;
559*1496Sbill 			}
560*1496Sbill 			cp1=regs[r]+1; cp2=lastrand;
561*1496Sbill 			if (OP2==(p->subop>>4)) {/* use 3 operand form of instruction */
562*1496Sbill 				p->pop=0;
563*1496Sbill 				p->subop += (OP3-OP2)<<4; lastrand=cp2=regs[RT3];
564*1496Sbill 			}
565*1496Sbill 			while (*cp2++= *cp1++);
566*1496Sbill 			if (p->op==MOVA && p->forw->op==PUSH) {
567*1496Sbill 				p->op=PUSHA; *regs[RT2]=0; p->pop=0;
568*1496Sbill 			} else if (p->op==MOV && p->forw->op==PUSH) {
569*1496Sbill 				p->op=PUSH ; *regs[RT2]=0; p->pop=0;
570*1496Sbill 			}
571*1496Sbill 			delnode(p->forw);
572*1496Sbill 			if (0<=(r2=isreg(lastrand)) && r2<NUSE) {
573*1496Sbill 				uses[r2]=uses[r]; uses[r]=0;
574*1496Sbill 			}
575*1496Sbill 			redun3(p,0);
576*1496Sbill 			newcode(p); redunm++; flow=r;
577*1496Sbill 		} else if (p->op==MOV && p->forw->op!=EXTV && p->forw->op!=EXTZV) {
578*1496Sbill 			/* superfluous fetch */
579*1496Sbill 			int nmatch;
580*1496Sbill 			char src[20];
581*1496Sbill 	movit:
582*1496Sbill 			cp2=src; cp1=regs[RT1]; while (*cp2++= *cp1++);
583*1496Sbill 			splitrand(p->forw);
584*1496Sbill 			if (p->forw->op != INC && p->forw->op != DEC)
585*1496Sbill 				lastrand=byondrd(p->forw);
586*1496Sbill 			nmatch=0;
587*1496Sbill 			for (preg=regs+RT1;*preg!=lastrand;preg++)
588*1496Sbill 				if (r==isreg(*preg)) {
589*1496Sbill 				cp2= *preg; cp1=src; while (*cp2++= *cp1++); ++nmatch;
590*1496Sbill 			}
591*1496Sbill 			if (nmatch==1) {
592*1496Sbill 				if (OP2==(p->forw->subop>>4) && equstr(src,regs[RT2])) {
593*1496Sbill 					p->forw->pop=0;
594*1496Sbill 					p->forw->subop += (OP3-OP2)<<4; cp1=regs[RT3];
595*1496Sbill 					*cp1++='r'; *cp1++=r+'0'; *cp1=0;
596*1496Sbill 				}
597*1496Sbill 				delnode(p); p=p->forw;
598*1496Sbill 				if (0<=(r2=isreg(src)) && r2<NUSE) {
599*1496Sbill 					uses[r2]=uses[r]; uses[r]=0;
600*1496Sbill 				}
601*1496Sbill 				redun3(p,0);
602*1496Sbill 				newcode(p); redunm++; flow=r;
603*1496Sbill 			} else splitrand(p);
604*1496Sbill 		}
605*1496Sbill 	} else if (p->op==MOV && (p->forw->op==CVT || p->forw->op==MOVZ)
606*1496Sbill 		&& p->forw->subop&0xf 	/* if base or index, then forget it */
607*1496Sbill 		&& compat(p->subop,p->forw->subop) && !source(cp1=regs[RT1])
608*1496Sbill 		&& !indexa(cp1)) goto movit;
609*1496Sbill 	}
610*1496Sbill 	/* adjust 'lastrand' past any 'read' or 'modify' operands. */
611*1496Sbill 	lastrand=byondrd(p);
612*1496Sbill 	/* a 'write' clobbers the register. */
613*1496Sbill 	if (0<=(r=isreg(lastrand)) && r<NUSE
614*1496Sbill 	|| OP2==(p->subop>>4) && 0<=(r=isreg(regs[RT2])) && r<NUSE && uses[r]==0) {
615*1496Sbill 		/* writing a dead register is useless, but watch side effects */
616*1496Sbill 		switch (p->op) {
617*1496Sbill 		case AOBLEQ: case AOBLSS: case SOBGTR: case SOBGEQ: break;
618*1496Sbill 		default: if (p->op==ACB) break;
619*1496Sbill 			if (uses[r]==0) {/* no direct uses, check for use of condition codes */
620*1496Sbill 				register struct node *q=p;
621*1496Sbill 				while ((q=nonlab(q->forw))->combop==JBR) q=q->ref;	/* cc unused, unchanged */
622*1496Sbill 				if (q->op!=CBR) {/* ... and destroyed */
623*1496Sbill 					preg=regs+RT1;
624*1496Sbill 					while (cp1= *preg++) {
625*1496Sbill 						if (cp1==lastrand) {redunm++; delnode(p); return(p->forw);}
626*1496Sbill 						if (source(cp1) || equstr(cp1,lastrand)) break;
627*1496Sbill 					}
628*1496Sbill 				}
629*1496Sbill 			}
630*1496Sbill 			flow=r;
631*1496Sbill 		}
632*1496Sbill 	}
633*1496Sbill 	if (0<=(r=flow)) {olduse=uses[r]; uses[r]=0; *(short *)(regs[r])=0;}
634*1496Sbill 		/* these two are here, rather than in bmove(),
635*1496Sbill 		/* because I decided that it was better to go for 3-address code
636*1496Sbill 		/* (save time) rather than fancy jbxx (save 1 byte)
637*1496Sbill 		/* on sequences like  bisl2 $64,r0; movl r0,foo
638*1496Sbill 		*/
639*1496Sbill 	if (p->op==BIC) {p=bicopt(p); splitrand(p); lastrand=byondrd(p);}
640*1496Sbill 	if (p->op==BIS) {bixprep(p,JBSS);           lastrand=byondrd(p);}
641*1496Sbill 	/* now look for 'read' or 'modify' (read & write) uses */
642*1496Sbill 	preg=regs+RT1;
643*1496Sbill 	while (*(cp1= *preg++)) {
644*1496Sbill 		/* check for  r  */
645*1496Sbill 		if (lastrand!=cp1 && 0<=(r=isreg(cp1)) && r<NUSE && uses[r]==0) {
646*1496Sbill 			uses[r]=p; cp2=regs[r]; *cp2++=p->subop;
647*1496Sbill 			if (p->op==MOV || p->op==PUSH || p->op==CVT || p->op==MOVZ || p->op==COM || p->op==NEG) {
648*1496Sbill 				if (p->op==PUSH) cp1="-(sp)";
649*1496Sbill 				else {
650*1496Sbill 					cp1=regs[RT2];
651*1496Sbill 					if (0<=(r=isreg(cp1)) && r<NUSE && uses[r]==0)
652*1496Sbill 						uses[r]=olduse; /* reincarnation!! */
653*1496Sbill 					/* as in  addl2 r0,r1;  movl r1,r0;  ret  */
654*1496Sbill 					if (p->op!=MOV) cp1=0;
655*1496Sbill 				}
656*1496Sbill 				if (cp1) while (*cp2++= *cp1++);
657*1496Sbill 			} else *cp2++=0;
658*1496Sbill 			continue;
659*1496Sbill 		}
660*1496Sbill 		/* check for (r),(r)+,-(r),[r] */
661*1496Sbill 		do if (*cp1=='(' || *cp1=='[') {/* get register number */
662*1496Sbill 			char t;
663*1496Sbill 			cp2= ++cp1; while (*++cp1!=')' && *cp1!=']'); t= *cp1; *cp1=0;
664*1496Sbill 			if (0<=(r=isreg(cp2)) && r<NUSE && (uses[r]==0 || uses[r]==p)) {
665*1496Sbill 				uses[r]=p; regs[r][0]=(*--cp2=='[' ? OPX<<4 : OPB<<4);
666*1496Sbill 			}
667*1496Sbill 			*cp1=t;
668*1496Sbill 		} while (*++cp1);
669*1496Sbill 	}
670*1496Sbill 	/* pushax or movax possibility? */
671*1496Sbill 	cp1=regs[RT1];
672*1496Sbill 	if (*cp1++=='$' && isstatic(cp1) && natural(regs[RT1])) {
673*1496Sbill 		if (p->combop==T(MOV,LONG)) {
674*1496Sbill 			if (regs[RT1][1]=='L' && 0!=(p->labno=getnum(regs[RT1]+2))) {
675*1496Sbill 				cp1=p->code; while (*cp1++!=','); p->code= --cp1;
676*1496Sbill 			}
677*1496Sbill 			p->combop=T(MOVA,LONG); ++p->code; p->pop=0;
678*1496Sbill 		} else if (p->combop==T(PUSH,LONG)) {
679*1496Sbill 			p->combop=T(PUSHA,LONG); ++p->code; p->pop=0;
680*1496Sbill 		} else if ((p->combop&0xFFFF)==T(ADD,U(LONG,OP3))
681*1496Sbill 				 && 0<=(r=isreg(regs[RT2]))) {
682*1496Sbill 			cp1=cp2=p->code; ++cp1;
683*1496Sbill 			do *cp2++= *cp1; while (*cp1++!=','); cp2[-1]='[';
684*1496Sbill 			do *cp2++= *cp1; while (*cp1++!=','); cp2[-1]=']';
685*1496Sbill 			if (!equstr(regs[RT3],"-(sp)")) p->combop=T(MOVA,BYTE);
686*1496Sbill 			else {p->combop=T(PUSHA,BYTE); *cp2=0;}
687*1496Sbill 			if (uses[r]==0) {uses[r]=p; regs[r][0]=OPX<<4;}
688*1496Sbill 			p->pop=0;
689*1496Sbill 		}
690*1496Sbill 	}
691*1496Sbill 	return(p);
692*1496Sbill }
693*1496Sbill 
694*1496Sbill ispow2(n) register long n; {/* -1 -> no; else -> log to base 2 */
695*1496Sbill 	register int log;
696*1496Sbill 	if (n==0 || n&(n-1)) return(-1); log=0;
697*1496Sbill 	for (;;) {n >>= 1; if (n==0) return(log); ++log; if (n== -1) return(log);}
698*1496Sbill }
699*1496Sbill 
700*1496Sbill bitopt(p) register struct node *p; {
701*1496Sbill 	/* change "bitx $<power_of_2>,a" followed by JEQ or JNE
702*1496Sbill 	/* into JBC or JBS.  watch out for I/O registers. (?)
703*1496Sbill 	/* assumes that 'splitrand' has already been called.
704*1496Sbill 	*/
705*1496Sbill 	register char *cp1,*cp2; int b;
706*1496Sbill 	cp1=regs[RT1]; cp2=regs[RT2];
707*1496Sbill 	if (*cp1++!='$' || !okio(cp2) || p->forw->op!=CBR || p->forw->subop&-2 ||
708*1496Sbill 		0>(b=ispow2(getnum(cp1))) ||
709*1496Sbill 		p->subop!=BYTE && (source(cp2) || indexa(cp2))) return;
710*1496Sbill 	if (b>=bitsize[p->subop]) {/* you dummy! */
711*1496Sbill 		if (source(cp2)) {/* side effect: auto increment or decrement */
712*1496Sbill 			p->pop=0;
713*1496Sbill 			p->op=TST; --cp1; while (*cp1++= *cp2++);
714*1496Sbill 			regs[RT2][0]=0; newcode(p);
715*1496Sbill 		} else delnode(p);
716*1496Sbill 		p = p->forw;
717*1496Sbill 		if (p->subop==JEQ) {p->combop=JBR; p->pop=0;}
718*1496Sbill 		else delnode(p);
719*1496Sbill 		nchange++; nbj++; return;
720*1496Sbill 	}
721*1496Sbill 	if (cp1=p->forw->code) {/* destination is not an internal label */
722*1496Sbill 		cp2=regs[RT3]; while (*cp2++= *cp1++);
723*1496Sbill 	}
724*1496Sbill 	if (b==0 && (p->subop==LONG || !indexa(regs[RT2]))) {/* JLB optimization, ala BLISS */
725*1496Sbill 		cp2=regs[RT1]; cp1=regs[RT2]; while (*cp2++= *cp1++);
726*1496Sbill 		cp2=regs[RT2]; cp1=regs[RT3]; while (*cp2++= *cp1++);
727*1496Sbill 		*(regs[RT3])=0; p->forw->subop += JLBC-JBC;
728*1496Sbill 		p->forw->pop=0;
729*1496Sbill 	} else {
730*1496Sbill 		cp1=regs[RT1]+1;
731*1496Sbill 		if (b>9) *cp1++= b/10 +'0'; *cp1++= b%10 +'0'; *cp1=0; /* $<bit_number> */
732*1496Sbill 	}
733*1496Sbill 	nbj++; newcode(p); p->combop = p->forw->combop+((JBC-JEQ)<<8);
734*1496Sbill 	p->labno = p->forw->labno; delnode(p->forw);
735*1496Sbill 	p->pop=0;
736*1496Sbill }
737*1496Sbill 
738*1496Sbill isfield(n) register long n; {/* -1 -> no; else -> position of low bit */
739*1496Sbill 	register int pos; register long t;
740*1496Sbill 	t= ((n-1)|n) +1;
741*1496Sbill 	if (n!=0 && (0==t || 0==n || 0<=ispow2(t))) {
742*1496Sbill 		pos=0; while(!(n&1)) {n >>= 1; ++pos;} return(pos);
743*1496Sbill 	} else return(-1);
744*1496Sbill }
745*1496Sbill 
746*1496Sbill bixprep(p,bix) register struct node *p; {
747*1496Sbill /* initial setup, single-bit checking for bisopt, bicopt.
748*1496Sbill /* return: 0->don't bother any more; 1->worthwhile trying
749*1496Sbill */
750*1496Sbill 	register char *cp1,*cp2;
751*1496Sbill 	splitrand(p); cp1=regs[RT1]; cp2=regs[RT2];
752*1496Sbill 	if (*cp1++!='$' || 0>(pos=isfield(f=getnum(cp1)))
753*1496Sbill 	  || !okio(cp2) || indexa(cp2) || source(cp2) || !okio(lastrand)) return(0);
754*1496Sbill 	f |= f-1; if (++f==0) siz=32-pos; else siz=ispow2(f)-pos;
755*1496Sbill 	if (siz==1 && pos>5 && (p->subop>>4)==OP2 && (p->subop&0xF)!=BYTE
756*1496Sbill 	  && pos<bitsize[p->subop&0xF]) {
757*1496Sbill 		p->ref = insertl(p->forw); p->combop = CBR | (bix<<8);
758*1496Sbill 		p->pop=0;
759*1496Sbill 		p->labno = p->ref->labno;
760*1496Sbill 		if (pos>9) {*cp1++= pos/10 +'0'; pos %= 10;}
761*1496Sbill 		*cp1++=pos+'0'; *cp1=0; newcode(p); nbj++; return(0);
762*1496Sbill 	}
763*1496Sbill 	return(1);
764*1496Sbill }
765*1496Sbill 
766*1496Sbill 
767*1496Sbill struct node *
768*1496Sbill bicopt(p) register struct node *p; {
769*1496Sbill /* use field operations or MOVZ if possible.  done as part of 'bflow'.
770*1496Sbill */
771*1496Sbill 	register char *cp1,*cp2; int r;
772*1496Sbill 	char src[50];
773*1496Sbill 	if (!bixprep(p,JBCC)) return(p);
774*1496Sbill 	if (f==0) {/* the BIC isolates low order bits */
775*1496Sbill 		siz=pos; pos=0;
776*1496Sbill 		if ((p->subop&0xF)==LONG && *(regs[RT2])!='$') {/* result of EXTZV is long */
777*1496Sbill 			/* save source of BICL in 'src' */
778*1496Sbill 			cp1=regs[RT2]; cp2=src; while (*cp2++= *cp1++);
779*1496Sbill 			if (p->back->op==ASH) {/* try for more */
780*1496Sbill 				splitrand(p->back); cp1=regs[RT1]; cp2=regs[RT3];
781*1496Sbill 				if (*cp1++=='$' && *(regs[RT2])!='$' && !indexa(regs[RT2])
782*1496Sbill 				  && 0>(f=getnum(cp1)) && equstr(src,cp2)
783*1496Sbill 				  && 0<=(r=isreg(cp2)) && r<NUSE) {/* a good ASH */
784*1496Sbill 					pos -= f; cp1=regs[RT2]; cp2=src; while (*cp2++= *cp1++);
785*1496Sbill 					delnode(p->back);
786*1496Sbill 				}
787*1496Sbill 			}
788*1496Sbill 			if (p->back->op==CVT || p->back->op==MOVZ) {/* greedy, aren't we? */
789*1496Sbill 				splitrand(p->back); cp1=regs[RT1]; cp2=regs[RT2];
790*1496Sbill 				if (equstr(src,cp2) && okio(cp1) && !indexa(cp1)
791*1496Sbill 				  && 0<=(r=isreg(cp2)) && r<NUSE
792*1496Sbill 				  && bitsize[p->back->subop&0xF]>=(pos+siz)
793*1496Sbill 				  && bitsize[p->back->subop>>4]>=(pos+siz)) {/* good CVT */
794*1496Sbill 					cp1=regs[RT1]; cp2=src; while (*cp2++= *cp1++);
795*1496Sbill 					delnode(p->back);
796*1496Sbill 				}
797*1496Sbill 			}
798*1496Sbill 			/* 'pos', 'siz' known; source of field is in 'src' */
799*1496Sbill 			splitrand(p); /* retrieve destination of BICL */
800*1496Sbill 			if (siz==8 && pos==0) {
801*1496Sbill 				p->combop = T(MOVZ,U(BYTE,LONG));
802*1496Sbill 				sprintf(line,"%s,%s",src,lastrand);
803*1496Sbill 			} else {
804*1496Sbill 				p->combop = T(EXTZV,LONG);
805*1496Sbill 				sprintf(line,"$%d,$%d,%s,%s",pos,siz,src,lastrand);
806*1496Sbill 			}
807*1496Sbill 			p->pop=0;
808*1496Sbill 			p->code = copy(line); nfield++; return(p);
809*1496Sbill 		}/* end EXTZV possibility */
810*1496Sbill 	}/* end low order bits */
811*1496Sbill /* unfortunately, INSV clears the condition codes, thus cannot be used */
812*1496Sbill /*	else {/* see if BICL2 of positive field should be INSV $0 */
813*1496Sbill /*		if (p->subop==(LONG | (OP2<<4)) && 6<=(pos+siz)) {
814*1496Sbill /*			p->combop = INSV;
815*1496Sbill /*			sprintf(line,"$0,$%d,$%d,%s",pos,siz,lastrand);
816*1496Sbill /*			p->code = copy(line); nfield++; return(p);
817*1496Sbill /*		}
818*1496Sbill /*	}
819*1496Sbill */
820*1496Sbill 	return(p);
821*1496Sbill }
822*1496Sbill 
823*1496Sbill jumpsw()
824*1496Sbill {
825*1496Sbill 	register struct node *p, *p1;
826*1496Sbill 	register t;
827*1496Sbill 	int nj;
828*1496Sbill 
829*1496Sbill 	t = 0;
830*1496Sbill 	nj = 0;
831*1496Sbill 	for (p=first.forw; p!=0; p = p->forw)
832*1496Sbill 		p->seq = ++t;
833*1496Sbill 	for (p=first.forw; p!=0; p = p1) {
834*1496Sbill 		p1 = p->forw;
835*1496Sbill 		if (p->op == CBR && p1->op==JBR && p->ref && p1->ref
836*1496Sbill 		 && abs(p->seq - p->ref->seq) > abs(p1->seq - p1->ref->seq)) {
837*1496Sbill 			if (p->ref==p1->ref)
838*1496Sbill 				continue;
839*1496Sbill 			p->subop = revbr[p->subop];
840*1496Sbill 			p->pop=0;
841*1496Sbill 			t = p1->ref;
842*1496Sbill 			p1->ref = p->ref;
843*1496Sbill 			p->ref = t;
844*1496Sbill 			t = p1->labno;
845*1496Sbill 			p1->labno = p->labno;
846*1496Sbill 			p->labno = t;
847*1496Sbill #ifdef COPYCODE
848*1496Sbill 			if (p->labno == 0) {
849*1496Sbill 				t = p1->code; p1->code = p->code; p->code = t;
850*1496Sbill 			}
851*1496Sbill #endif
852*1496Sbill 			nrevbr++;
853*1496Sbill 			nj++;
854*1496Sbill 		}
855*1496Sbill 	}
856*1496Sbill 	return(nj);
857*1496Sbill }
858*1496Sbill 
859*1496Sbill addsob()
860*1496Sbill {
861*1496Sbill 	register struct node *p, *p1, *p2, *p3;
862*1496Sbill 
863*1496Sbill 	for (p = &first; (p1 = p->forw)!=0; p = p1) {
864*1496Sbill 	if (p->combop==T(DEC,LONG) && p1->op==CBR) {
865*1496Sbill 		if (abs(p->seq - p1->ref->seq) > 12) continue;
866*1496Sbill 		if (p1->subop==JGE || p1->subop==JGT) {
867*1496Sbill 			if (p1->subop==JGE) p->combop=SOBGEQ; else p->combop=SOBGTR;
868*1496Sbill 			p->pop=0;
869*1496Sbill 			p->labno = p1->labno; delnode(p1); nsob++;
870*1496Sbill 		}
871*1496Sbill 	} else if (p->combop==T(INC,LONG)) {
872*1496Sbill 		if (p1->op==LABEL && p1->refc==1 && p1->forw->combop==T(CMP,LONG)
873*1496Sbill 		  && (p2=p1->forw->forw)->combop==T(CBR,JLE)
874*1496Sbill 		  && (p3=p2->ref->back)->combop==JBR && p3->ref==p1
875*1496Sbill 		  && p3->forw->op==LABEL && p3->forw==p2->ref) {
876*1496Sbill 			/* change	INC LAB: CMP	to	LAB: INC CMP */
877*1496Sbill 			p->back->forw=p1; p1->back=p->back;
878*1496Sbill 			p->forw=p1->forw; p1->forw->back=p;
879*1496Sbill 			p->back=p1; p1->forw=p;
880*1496Sbill 			p1=p->forw;
881*1496Sbill 			/* adjust beginning value by 1 */
882*1496Sbill 				p2=alloc(sizeof first); p2->combop=T(DEC,LONG);
883*1496Sbill 				p2->pop=0;
884*1496Sbill 				p2->forw=p3; p2->back=p3->back; p3->back->forw=p2;
885*1496Sbill 				p3->back=p2; p2->code=p->code; p2->labno=0;
886*1496Sbill 		}
887*1496Sbill 		if (p1->combop==T(CMP,LONG) && (p2=p1->forw)->op==CBR) {
888*1496Sbill 			register char *cp1,*cp2;
889*1496Sbill 			splitrand(p1); if (!equstr(p->code,regs[RT1])) continue;
890*1496Sbill 			if (abs(p->seq - p2->ref->seq)>12) {/* outside byte displ range */
891*1496Sbill 				if (p2->subop!=JLE) continue;
892*1496Sbill 				p->combop=T(ACB,LONG);
893*1496Sbill 				cp2=regs[RT1]; cp1=regs[RT2]; while (*cp2++= *cp1++); /* limit */
894*1496Sbill 				cp2=regs[RT2]; cp1="$1"; while (*cp2++= *cp1++); /* increment */
895*1496Sbill 				cp2=regs[RT3]; cp1=p->code; while (*cp2++= *cp1++); /* index */
896*1496Sbill 				p->pop=0; newcode(p);
897*1496Sbill 				p->labno = p2->labno; delnode(p2); delnode(p1); nsob++;
898*1496Sbill 			} else if (p2->subop==JLE || p2->subop==JLT) {
899*1496Sbill 				if (p2->subop==JLE) p->combop=AOBLEQ; else p->combop=AOBLSS;
900*1496Sbill 				cp2=regs[RT1]; cp1=regs[RT2]; while (*cp2++= *cp1++); /* limit */
901*1496Sbill 				cp2=regs[RT2]; cp1=p->code; while (*cp2++= *cp1++); /* index */
902*1496Sbill 				p->pop=0; newcode(p);
903*1496Sbill 				p->labno = p2->labno; delnode(p2); delnode(p1); nsob++;
904*1496Sbill 			}
905*1496Sbill 		}
906*1496Sbill 	}
907*1496Sbill 	}
908*1496Sbill }
909*1496Sbill 
910*1496Sbill abs(x)
911*1496Sbill {
912*1496Sbill 	return(x<0? -x: x);
913*1496Sbill }
914*1496Sbill 
915*1496Sbill equop(p1, p2)
916*1496Sbill register struct node *p1;
917*1496Sbill struct node *p2;
918*1496Sbill {
919*1496Sbill 	register char *cp1, *cp2;
920*1496Sbill 
921*1496Sbill 	if (p1->combop != p2->combop)
922*1496Sbill 		return(0);
923*1496Sbill 	if (p1->op>0 && p1->op<MOV)
924*1496Sbill 		return(0);
925*1496Sbill 	if (p1->op==MOVA && p1->labno!=p2->labno) return(0);
926*1496Sbill 	cp1 = p1->code;
927*1496Sbill 	cp2 = p2->code;
928*1496Sbill 	if (cp1==0 && cp2==0)
929*1496Sbill 		return(1);
930*1496Sbill 	if (cp1==0 || cp2==0)
931*1496Sbill 		return(0);
932*1496Sbill 	while (*cp1 == *cp2++)
933*1496Sbill 		if (*cp1++ == 0)
934*1496Sbill 			return(1);
935*1496Sbill 	return(0);
936*1496Sbill }
937*1496Sbill 
938*1496Sbill delnode(p) register struct node *p; {
939*1496Sbill 	p->back->forw = p->forw;
940*1496Sbill 	p->forw->back = p->back;
941*1496Sbill }
942*1496Sbill 
943*1496Sbill decref(p)
944*1496Sbill register struct node *p;
945*1496Sbill {
946*1496Sbill 	if (p && --p->refc <= 0) {
947*1496Sbill 		nrlab++;
948*1496Sbill 		delnode(p);
949*1496Sbill 	}
950*1496Sbill }
951*1496Sbill 
952*1496Sbill struct node *
953*1496Sbill nonlab(ap)
954*1496Sbill struct node *ap;
955*1496Sbill {
956*1496Sbill 	register struct node *p;
957*1496Sbill 
958*1496Sbill 	p = ap;
959*1496Sbill 	while (p && p->op==LABEL)
960*1496Sbill 		p = p->forw;
961*1496Sbill 	return(p);
962*1496Sbill }
963*1496Sbill 
964*1496Sbill clearuse() {
965*1496Sbill 	register struct node **i;
966*1496Sbill 	for (i=uses+NUSE; i>uses;) *--i=0;
967*1496Sbill }
968*1496Sbill 
969*1496Sbill clearreg() {
970*1496Sbill 	register short **i;
971*1496Sbill 	for (i=regs+NREG; i>regs;) **--i=0;
972*1496Sbill 	conloc[0] = 0; ccloc[0] = 0;
973*1496Sbill }
974*1496Sbill 
975*1496Sbill savereg(ai, s, type)
976*1496Sbill register char *s;
977*1496Sbill {
978*1496Sbill 	register char *p, *sp;
979*1496Sbill 
980*1496Sbill 	sp = p = regs[ai];
981*1496Sbill 	if (source(s)) /* side effects in addressing */
982*1496Sbill 		return;
983*1496Sbill 	/* if any indexing, must be parameter or local */
984*1496Sbill 	/* indirection (as in "*-4(fp)") is ok, however */
985*1496Sbill 	*p++ = type;
986*1496Sbill 	while (*p++ = *s)
987*1496Sbill 		if (*s=='[' || *s++=='(' && *s!='a' && *s!='f') {*sp = 0; return;}
988*1496Sbill }
989*1496Sbill 
990*1496Sbill dest(s,type)
991*1496Sbill register char *s;
992*1496Sbill {
993*1496Sbill 	register int i;
994*1496Sbill 
995*1496Sbill 	source(s); /* handle addressing side effects */
996*1496Sbill 	if ((i = isreg(s)) >= 0) {
997*1496Sbill 		*(short *)(regs[i]) = 0; /* if register destination, that reg is a goner */
998*1496Sbill 		if (DOUBLE==(type&0xF) || DOUBLE==((type>>4)&0xF))
999*1496Sbill 			*(short *)(regs[i+1]) = 0; /* clobber two at once */
1000*1496Sbill 	}
1001*1496Sbill 	for (i=NREG; --i>=0;)
1002*1496Sbill 		if (regs[i][1]=='*' && equstr(s, regs[i]+2))
1003*1496Sbill 			*(short *)(regs[i]) = 0; /* previous indirection through destination is invalid */
1004*1496Sbill 	while ((i = findrand(s,0)) >= 0) /* previous values of destination are invalid */
1005*1496Sbill 		*(short *)(regs[i]) = 0;
1006*1496Sbill 	if (!natural(s)) {/* wild store, everything except constants vanishes */
1007*1496Sbill 		for (i=NREG; --i>=0;) if (regs[i][1] != '$') *(short *)(regs[i]) = 0;
1008*1496Sbill 		conloc[0] = 0; ccloc[0] = 0;
1009*1496Sbill 	} else setcc(s,type); /* natural destinations set condition codes */
1010*1496Sbill }
1011*1496Sbill 
1012*1496Sbill splitrand(p) struct node *p; {
1013*1496Sbill /* separate operands at commas, set up 'regs' and 'lastrand' */
1014*1496Sbill register char *p1, *p2; register char **preg;
1015*1496Sbill preg=regs+RT1;
1016*1496Sbill if (p1=p->code) while (*p1) {
1017*1496Sbill 	lastrand=p2= *preg++;
1018*1496Sbill 	while (*p1) if (','==(*p2++= *p1++)) {--p2; break;}
1019*1496Sbill 	*p2=0;
1020*1496Sbill }
1021*1496Sbill while (preg<(regs+RT1+5)) *(*preg++)=0;
1022*1496Sbill }
1023*1496Sbill 
1024*1496Sbill compat(have, want) {
1025*1496Sbill register int hsrc, hdst;
1026*1496Sbill if (0==(want &= 0xF)) return(1); /* anything satisfies a wildcard want */
1027*1496Sbill hsrc=have&0xF; if (0==(hdst=((have>>4)&0xF)) || hdst>=OP2) hdst=hsrc;
1028*1496Sbill if (want>=FLOAT) return(hdst==want && hsrc==want);
1029*1496Sbill 	/* FLOAT, DOUBLE not compat: rounding */
1030*1496Sbill return(hsrc>=want && hdst>=want && hdst<FLOAT);
1031*1496Sbill }
1032*1496Sbill 
1033*1496Sbill equtype(t1,t2) {return(compat(t1,t2) && compat(t2,t1));}
1034*1496Sbill 
1035*1496Sbill findrand(as, type)
1036*1496Sbill char *as;
1037*1496Sbill {
1038*1496Sbill 	register char **i;
1039*1496Sbill 	for (i = regs+NREG; --i>=regs;) {
1040*1496Sbill 		if (**i && equstr(*i+1, as) && compat(**i,type))
1041*1496Sbill 			return(i-regs);
1042*1496Sbill 	}
1043*1496Sbill 	return(-1);
1044*1496Sbill }
1045*1496Sbill 
1046*1496Sbill isreg(s)
1047*1496Sbill register char *s;
1048*1496Sbill {
1049*1496Sbill 	if (*s++!='r' || !isdigit(*s++)) return(-1);
1050*1496Sbill 	if (*s==0) return(*--s-'0');
1051*1496Sbill 	if (*(s-1)=='1' && isdigit(*s++) && *s==0) return(10+*--s-'0');
1052*1496Sbill 	return(-1);
1053*1496Sbill }
1054*1496Sbill 
1055*1496Sbill check()
1056*1496Sbill {
1057*1496Sbill 	register struct node *p, *lp;
1058*1496Sbill 
1059*1496Sbill 	lp = &first;
1060*1496Sbill 	for (p=first.forw; p!=0; p = p->forw) {
1061*1496Sbill 		if (p->back != lp)
1062*1496Sbill 			abort(-1);
1063*1496Sbill 		lp = p;
1064*1496Sbill 	}
1065*1496Sbill }
1066*1496Sbill 
1067*1496Sbill source(ap)
1068*1496Sbill char *ap;
1069*1496Sbill {
1070*1496Sbill 	register char *p1, *p2;
1071*1496Sbill 
1072*1496Sbill 	p1 = ap;
1073*1496Sbill 	p2 = p1;
1074*1496Sbill 	if (*p1==0)
1075*1496Sbill 		return(0);
1076*1496Sbill 	while (*p2++ && *(p2-1)!='[');
1077*1496Sbill 	if (*p1=='-' && *(p1+1)=='('
1078*1496Sbill 	 || *p1=='*' && *(p1+1)=='-' && *(p1+2)=='('
1079*1496Sbill 	 || *(p2-2)=='+') {
1080*1496Sbill 		while (*p1 && *p1++!='r');
1081*1496Sbill 		if (isdigit(*p1++))
1082*1496Sbill 			if (isdigit(*p1)) *(short *)(regs[10+*p1-'0'])=0;
1083*1496Sbill 			else *(short *)(regs[*--p1-'0'])=0;
1084*1496Sbill 		return(1);
1085*1496Sbill 	}
1086*1496Sbill 	return(0);
1087*1496Sbill }
1088*1496Sbill 
1089*1496Sbill newcode(p) struct node *p; {
1090*1496Sbill 	register char *p1,*p2,**preg;
1091*1496Sbill 	preg=regs+RT1; p2=line;
1092*1496Sbill 	while (*(p1= *preg++)) {while (*p2++= *p1++); *(p2-1)=',';}
1093*1496Sbill 	*--p2=0;
1094*1496Sbill 	p->code=copy(line);
1095*1496Sbill }
1096*1496Sbill 
1097*1496Sbill repladdr(p)
1098*1496Sbill struct node *p;
1099*1496Sbill {
1100*1496Sbill 	register r;
1101*1496Sbill 	register char *p1, *p2;
1102*1496Sbill 	char **preg; int nrepl;
1103*1496Sbill 
1104*1496Sbill 	preg=regs+RT1; nrepl=0;
1105*1496Sbill 	while (lastrand!=(p1= *preg++))
1106*1496Sbill 		if (!source(p1) && 0<=(r=findrand(p1,p->subop))) {
1107*1496Sbill 			*p1++='r'; if (r>9) {*p1++='1'; r -= 10;} *p1++=r+'0'; *p1=0;
1108*1496Sbill 			nrepl++; nsaddr++;
1109*1496Sbill 		}
1110*1496Sbill 	if (nrepl) newcode(p);
1111*1496Sbill }
1112*1496Sbill 
1113*1496Sbill /* movedat()
1114*1496Sbill /* {
1115*1496Sbill /* 	register struct node *p1, *p2;
1116*1496Sbill /* 	struct node *p3;
1117*1496Sbill /* 	register seg;
1118*1496Sbill /* 	struct node data;
1119*1496Sbill /* 	struct node *datp;
1120*1496Sbill /*
1121*1496Sbill /* 	if (first.forw == 0)
1122*1496Sbill /* 		return;
1123*1496Sbill /* 	datp = &data;
1124*1496Sbill /* 	for (p1 = first.forw; p1!=0; p1 = p1->forw) {
1125*1496Sbill /* 		if (p1->op == DATA) {
1126*1496Sbill /* 			p2 = p1->forw;
1127*1496Sbill /* 			while (p2 && p2->op!=TEXT)
1128*1496Sbill /* 				p2 = p2->forw;
1129*1496Sbill /* 			if (p2==0)
1130*1496Sbill /* 				break;
1131*1496Sbill /* 			p3 = p1->back;
1132*1496Sbill /* 			p1->back->forw = p2->forw;
1133*1496Sbill /* 			p2->forw->back = p3;
1134*1496Sbill /* 			p2->forw = 0;
1135*1496Sbill /* 			datp->forw = p1;
1136*1496Sbill /* 			p1->back = datp;
1137*1496Sbill /* 			p1 = p3;
1138*1496Sbill /* 			datp = p2;
1139*1496Sbill /* 		}
1140*1496Sbill /* 	}
1141*1496Sbill /* 	if (data.forw) {
1142*1496Sbill /* 		datp->forw = first.forw;
1143*1496Sbill /* 		first.forw->back = datp;
1144*1496Sbill /* 		data.forw->back = &first;
1145*1496Sbill /* 		first.forw = data.forw;
1146*1496Sbill /* 	}
1147*1496Sbill /* 	seg = -1;
1148*1496Sbill /* 	for (p1 = first.forw; p1!=0; p1 = p1->forw) {
1149*1496Sbill /* 		if (p1->op==TEXT||p1->op==DATA||p1->op==BSS) {
1150*1496Sbill /* 			if (p1->op == seg || p1->forw&&p1->forw->op==seg) {
1151*1496Sbill /* 				p1->back->forw = p1->forw;
1152*1496Sbill /* 				p1->forw->back = p1->back;
1153*1496Sbill /* 				p1 = p1->back;
1154*1496Sbill /* 				continue;
1155*1496Sbill /* 			}
1156*1496Sbill /* 			seg = p1->op;
1157*1496Sbill /* 		}
1158*1496Sbill /* 	}
1159*1496Sbill /* }
1160*1496Sbill */
1161*1496Sbill 
1162*1496Sbill redunbr(p)
1163*1496Sbill register struct node *p;
1164*1496Sbill {
1165*1496Sbill 	register struct node *p1;
1166*1496Sbill 	register char *ap1;
1167*1496Sbill 	char *ap2;
1168*1496Sbill 
1169*1496Sbill 	if ((p1 = p->ref) == 0)
1170*1496Sbill 		return;
1171*1496Sbill 	p1 = nonlab(p1);
1172*1496Sbill 	if (p1->op==TST) {
1173*1496Sbill 		splitrand(p1);
1174*1496Sbill 		savereg(RT2, "$0", p1->subop);
1175*1496Sbill 	} else if (p1->op==CMP)
1176*1496Sbill 		splitrand(p1);
1177*1496Sbill 	else
1178*1496Sbill 		return;
1179*1496Sbill 	if (p1->forw->op==CBR) {
1180*1496Sbill 		ap1 = findcon(RT1, p1->subop);
1181*1496Sbill 		ap2 = findcon(RT2, p1->subop);
1182*1496Sbill 		p1 = p1->forw;
1183*1496Sbill 		if (compare(p1->subop, ap1, ap2)) {
1184*1496Sbill 			nredunj++;
1185*1496Sbill 			nchange++;
1186*1496Sbill 			decref(p->ref);
1187*1496Sbill 			p->ref = p1->ref;
1188*1496Sbill 			p->labno = p1->labno;
1189*1496Sbill #ifdef COPYCODE
1190*1496Sbill 			if (p->labno == 0)
1191*1496Sbill 				p->code = p1->code;
1192*1496Sbill 			if (p->ref)
1193*1496Sbill #endif
1194*1496Sbill 				p->ref->refc++;
1195*1496Sbill 		}
1196*1496Sbill 	} else if (p1->op==TST && equstr(regs[RT1],ccloc+1) &&
1197*1496Sbill 			equtype(ccloc[0],p1->subop)) {
1198*1496Sbill 		p1=insertl(p1->forw); decref(p->ref); p->ref=p1;
1199*1496Sbill 		nrtst++; nchange++;
1200*1496Sbill 	}
1201*1496Sbill }
1202*1496Sbill 
1203*1496Sbill char *
1204*1496Sbill findcon(i, type)
1205*1496Sbill {
1206*1496Sbill 	register char *p;
1207*1496Sbill 	register r;
1208*1496Sbill 
1209*1496Sbill 	p = regs[i];
1210*1496Sbill 	if (*p=='$')
1211*1496Sbill 		return(p);
1212*1496Sbill 	if ((r = isreg(p)) >= 0 && compat(regs[r][0],type))
1213*1496Sbill 		return(regs[r]+1);
1214*1496Sbill 	if (equstr(p, conloc))
1215*1496Sbill 		return(conval+1);
1216*1496Sbill 	return(p);
1217*1496Sbill }
1218*1496Sbill 
1219*1496Sbill compare(op, acp1, acp2)
1220*1496Sbill char *acp1, *acp2;
1221*1496Sbill {
1222*1496Sbill 	register char *cp1, *cp2;
1223*1496Sbill 	register n1;
1224*1496Sbill 	int n2;	int sign;
1225*1496Sbill 
1226*1496Sbill 	cp1 = acp1;
1227*1496Sbill 	cp2 = acp2;
1228*1496Sbill 	if (*cp1++ != '$' || *cp2++ != '$')
1229*1496Sbill 		return(0);
1230*1496Sbill 	n1 = 0; sign=1; if (*cp2=='-') {++cp2; sign= -1;}
1231*1496Sbill 	while (isdigit(*cp2)) {n1 *= 10; n1 += (*cp2++ - '0')*sign;}
1232*1496Sbill 	n2 = n1;
1233*1496Sbill 	n1 = 0; sign=1; if (*cp1=='-') {++cp1; sign= -1;}
1234*1496Sbill 	while (isdigit(*cp1)) {n1 *= 10; n1 += (*cp1++ - '0')*sign;}
1235*1496Sbill 	if (*cp1=='+')
1236*1496Sbill 		cp1++;
1237*1496Sbill 	if (*cp2=='+')
1238*1496Sbill 		cp2++;
1239*1496Sbill 	do {
1240*1496Sbill 		if (*cp1++ != *cp2)
1241*1496Sbill 			return(0);
1242*1496Sbill 	} while (*cp2++);
1243*1496Sbill 	cp1 = n1;
1244*1496Sbill 	cp2 = n2;
1245*1496Sbill 	switch(op) {
1246*1496Sbill 
1247*1496Sbill 	case JEQ:
1248*1496Sbill 		return(cp1 == cp2);
1249*1496Sbill 	case JNE:
1250*1496Sbill 		return(cp1 != cp2);
1251*1496Sbill 	case JLE:
1252*1496Sbill 		return(((int)cp1) <= ((int)cp2));
1253*1496Sbill 	case JGE:
1254*1496Sbill 		return(((int)cp1) >= ((int)cp2));
1255*1496Sbill 	case JLT:
1256*1496Sbill 		return(((int)cp1) < ((int)cp2));
1257*1496Sbill 	case JGT:
1258*1496Sbill 		return(((int)cp1) > ((int)cp2));
1259*1496Sbill 	case JLO:
1260*1496Sbill 		return(cp1 < cp2);
1261*1496Sbill 	case JHI:
1262*1496Sbill 		return(cp1 > cp2);
1263*1496Sbill 	case JLOS:
1264*1496Sbill 		return(cp1 <= cp2);
1265*1496Sbill 	case JHIS:
1266*1496Sbill 		return(cp1 >= cp2);
1267*1496Sbill 	}
1268*1496Sbill 	return(0);
1269*1496Sbill }
1270*1496Sbill 
1271*1496Sbill setcon(cv, cl, type)
1272*1496Sbill register char *cv, *cl;
1273*1496Sbill {
1274*1496Sbill 	register char *p;
1275*1496Sbill 
1276*1496Sbill 	if (*cv != '$')
1277*1496Sbill 		return;
1278*1496Sbill 	if (!natural(cl))
1279*1496Sbill 		return;
1280*1496Sbill 	p = conloc;
1281*1496Sbill 	while (*p++ = *cl++);
1282*1496Sbill 	p = conval;
1283*1496Sbill 	*p++ = type;
1284*1496Sbill 	while (*p++ = *cv++);
1285*1496Sbill }
1286*1496Sbill 
1287*1496Sbill equstr(p1, p2)
1288*1496Sbill register char *p1, *p2;
1289*1496Sbill {
1290*1496Sbill 	do {
1291*1496Sbill 		if (*p1++ != *p2)
1292*1496Sbill 			return(0);
1293*1496Sbill 	} while (*p2++);
1294*1496Sbill 	return(1);
1295*1496Sbill }
1296*1496Sbill 
1297*1496Sbill setcc(ap,type)
1298*1496Sbill char *ap;
1299*1496Sbill {
1300*1496Sbill 	register char *p, *p1;
1301*1496Sbill 
1302*1496Sbill 	p = ap;
1303*1496Sbill 	if (!natural(p)) {
1304*1496Sbill 		ccloc[0] = 0;
1305*1496Sbill 		return;
1306*1496Sbill 	}
1307*1496Sbill 	p1 = ccloc;
1308*1496Sbill 	*p1++ = type;
1309*1496Sbill 	while (*p1++ = *p++);
1310*1496Sbill }
1311*1496Sbill 
1312*1496Sbill okio(p) register char *p; {/* 0->probable I/O space address; 1->not */
1313*1496Sbill 	if (ioflag && (!natural(p) || 0>getnum(p))) return(0);
1314*1496Sbill 	return(1);
1315*1496Sbill }
1316*1496Sbill 
1317*1496Sbill indexa(p) register char *p; {/* 1-> uses [r] addressing mode; 0->doesn't */
1318*1496Sbill 	while (*p) if (*p++=='[') return(1);
1319*1496Sbill 	return(0);
1320*1496Sbill }
1321*1496Sbill 
1322*1496Sbill natural(p)
1323*1496Sbill register char *p;
1324*1496Sbill {/* 1->simple local, parameter, global, or register; 0->otherwise */
1325*1496Sbill 	if (*p=='*' || *p=='(' || *p=='-'&&*(p+1)=='(' || *p=='$'&&getnum(p+1))
1326*1496Sbill 		return(0);
1327*1496Sbill 	while (*p++);
1328*1496Sbill 	p--;
1329*1496Sbill 	if (*--p=='+' || *p==']' || *p==')' && *(p-2)!='a' && *(p-2)!='f')
1330*1496Sbill 		return(0);
1331*1496Sbill 	return(1);
1332*1496Sbill }
1333*1496Sbill 
1334*1496Sbill /*
1335*1496Sbill ** Tell if an argument is most likely static.
1336*1496Sbill */
1337*1496Sbill 
1338*1496Sbill isstatic(cp)
1339*1496Sbill register char	*cp;
1340*1496Sbill {
1341*1496Sbill 	if (*cp == '_' || *cp == 'L' || (*cp++ == 'v' && *cp == '.'))
1342*1496Sbill 		return (1);
1343*1496Sbill 	return (0);
1344*1496Sbill }
1345