xref: /original-bsd/usr.bin/f77/pass1.vax/optcse.c (revision 7bad34b3)
1 /*-
2  * Copyright (c) 1980 The Regents of the University of California.
3  * All rights reserved.
4  *
5  * %sccs.include.proprietary.c%
6  */
7 
8 #ifndef lint
9 static char sccsid[] = "@(#)optcse.c	5.3 (Berkeley) 04/12/91";
10 #endif /* not lint */
11 
12 /*
13  * optcse.c
14  *
15  * Common subexpression elimination routines, F77 compiler pass 1.
16  *
17  * University of Utah CS Dept modification history:
18  *
19  * $Log:	optcse.c,v $
20  * Revision 2.4  84/10/29  04:40:48  donn
21  * Problem with conversions -- two expressions headed by a conversion may be
22  * identical in structure but different in type, thus type must be checked in
23  * findnode().  This was causing a subscript to become REAL*8 type...
24  *
25  * Revision 2.3  84/08/04  20:38:53  donn
26  * Added fix from Jerry Berkman for an earlier fix from Alastair Fyfe --
27  * samebase() should treat EQUIVALENCEd variables just as daintily as
28  * COMMON variables.
29  *
30  * Revision 2.2  84/08/01  16:04:33  donn
31  * Changed rmcommaop so that it does subscripts too.
32  *
33  * Revision 2.1  84/07/19  12:03:44  donn
34  * Changed comment headers for UofU.
35  *
36  * Revision 1.5  84/07/09  14:43:05  donn
37  * Added changes to make OPPLUSEQ and OPSTAREQ expressions ineligible for
38  * CSE, since I can't think of a simple way to handle them and they are broken
39  * in the previous version, where they were treated like OPASSIGN -- this
40  * fails because CSE would think that the value of the lhs and rhs were equal.
41  *
42  * Revision 1.4  84/06/08  11:43:35  donn
43  * Yet another way of handling the bug with COMMON -- this one is from Alastair
44  * Fyfe at Sun.  I backed out the old fix.
45  *
46  * Revision 1.3  84/03/07  19:25:14  donn
47  * Changed method of handling COMMON bug -- COMMON variables are now treated
48  * like array elements and hence are ineligible for CSE.
49  *
50  * Revision 1.2  84/02/26  03:30:47  donn
51  * Fixed bug in evaluation graph construction that caused two variables in
52  * common to be considered identical if they were merely in the same common,
53  * rather than in the same common at the same offset.
54  *
55  */
56 
57 #include "defs.h"
58 #include "optim.h"
59 
60 #define FALSE	0
61 #define TRUE	1
62 
63 LOCAL Bblockp	current_BB;
64 LOCAL int	cse1count;	/* count of number of cse uses eliminated */
65 LOCAL int	cse2count;	/* count of number of cse def's eliminated */
66 
67 
68 
69 
70 LOCAL dumpstacks()
71 {
72 	duplptr dl;
73 	valuen p;
74 	idlptr idl;
75 	idptr idp;
76 	nodelptr nl;
77 	int i;
78 
79 	fprintf(diagfile,"\n *** IDblocks ***\n");
80 	for(idp=current_BB->headid;idp;idp=idp->next)
81 	{
82 		fprintf(diagfile,
83 			"idp= %d idaddr= %d initval= %d assgnval= %d \n",
84 			idp, idp->idaddr, idp->initval, idp->assgnval);
85 		fprintf(diagfile,"nodes: ");
86 		i=0;
87 		for (nl=idp->headnodelist;nl;nl=nl->next) {
88 			if(++i>20){
89 				fprintf(diagfile,"\n");
90 				i=0;
91 			}
92 			fprintf(diagfile," %d ",nl->nodep);
93 		}
94 		fprintf(diagfile,"\n");
95 	}
96 
97 	fprintf(diagfile,"\n *** VALUE NODES *** \n");
98 	for(p=current_BB->headnode;p;p=p->next) {
99 		fprintf(diagfile,
100 		   "\np= %d opp= %d lc= %d rc= %d rs= %d is_dead= %d n_dups %d",
101 		   p, p->opp,p->lc,p->rc, p->rs, p->is_dead, p->n_dups);
102 		if (p->rs){
103 			fprintf(diagfile,"tag= %d ",p->opp->tag);
104 			if(p->opp->tag==TEXPR)
105 				fprintf(diagfile,"opco= %d ",
106 				    p->opp->exprblock.opcode);
107 		}
108 		fprintf(diagfile,"\n");
109 		fprintf(diagfile,"parent= %d dups:  ",p->parent);
110 		i=0;
111 		for(dl=p->headduplist;dl;dl=dl->next) {
112 			if(++i>20){
113 				fprintf(diagfile,"\n");
114 				i=0;
115 			}
116 			fprintf(diagfile," %d ",dl->parent);
117 		}
118 
119 		fprintf(diagfile,"\ndeps IDs");
120 		i=0;
121 		for(idl=p->headdeplist;idl;idl=idl->next) {
122 			if(++i>20){
123 				fprintf(diagfile,"\n");
124 				i=0;
125 			}
126 			fprintf(diagfile," %d ",idl->idp);
127 		}
128 	}
129 }
130 
131 
132 
133 LOCAL idlptr mergedeps(lnode,rnode)
134 valuen lnode,rnode;
135 /* Given two value nodes, merge the lists of identifiers on which they
136 ** depend to produce a new list incorporating both dependencies. Lists
137 ** are assumed to be ordered by increasing idp address. No duplicate identifiers
138 ** are generated in the output list.
139 */
140 {
141 	register idlptr lp,lp1,lp2;
142 	idlptr head;
143 
144 	lp = lp1 = lp2 = head = NULL;
145 	if(lnode) lp1 = lnode->headdeplist;
146 	if(rnode) lp2 = rnode->headdeplist;
147 
148 	while (lp1 || lp2) {
149 		if (lp) {
150 			lp->next = ALLOC(IDlist);
151 			lp = lp->next;
152 		}
153 		else lp = head = ALLOC(IDlist);
154 		lp->next = 0;
155 		if (lp1 == 0) {
156 			lp->idp = lp2->idp;
157 			lp2 = lp2->next;
158 		}
159 		else if (lp2 == 0) {
160 			lp->idp = lp1->idp;
161 			lp1 = lp1->next;
162 		}
163 		else if (lp1->idp < lp2->idp) {
164 			lp->idp = lp1->idp;
165 			lp1 = lp1->next;
166 		}
167 		else if (lp1->idp > lp2->idp) {
168 			lp->idp = lp2->idp;
169 			lp2 = lp2->next;
170 		}
171 		else {
172 			lp->idp = lp1->idp;
173 			lp1 = lp1->next;
174 			lp2 = lp2->next;
175 		}
176 	}
177 	return(head);
178 }
179 
180 
181 
182 LOCAL removenode(nodep)
183 valuen nodep;
184 /*  Removes a value node from every IDblock on the node's list of identifiers.
185 */
186 {
187 	register idlptr idl;
188 	register nodelptr nl;
189 	register nodelptr *addrnl;
190 
191 	if(nodep == NULL) return ;
192 
193 	/* loop through all identifiers */
194 	for(idl=nodep->headdeplist;idl;idl=idl->next)
195 	{
196 		addrnl = &(idl->idp->headnodelist);
197 		/* for each identifier loop through all nodes until match is found */
198 		for(nl = *addrnl; nl; nl = *addrnl)
199 		{
200 			if(nl->nodep == nodep) {
201 				*addrnl = nl->next;
202 				free ( (charptr) nl );
203 				break;
204 			}
205 			addrnl = &nl->next;
206 		}
207 	}
208 	nodep->is_dead = TRUE;
209 }
210 
211 
212 
213 LOCAL killid(idp)
214 idptr idp;
215 /* Kill all nodes on one identifier's list of dependent nodes, i.e. remove
216 ** all calculations that depend on this identifier from the available
217 ** values stack.  Free the list of records pointing at the dependent nodes.
218 */
219 {
220 	nodelptr nl1,nl2;
221 
222 	for (nl1 = idp->headnodelist; nl1; nl1=nl2)
223 	{
224 		nl2 = nl1->next;
225 		removenode(nl1->nodep);
226 	}
227 	/* the above call frees the node list record pointed at by nl1 since it frees
228 	** all the node list records that reference the value node being killed
229 	*/
230 	idp->headnodelist = NULL;
231 
232 }
233 
234 
235 
236 LOCAL killdepnodes(idp)
237 idptr idp;
238 /* Kill all value nodes that represent calculations which depend on
239 ** this identifier. If the identifier is in COMMON or EQUIVALENCE storage,
240 ** kill all values that depend on identifiers in COMMON or EQUIVALENCE
241 */
242 {
243 	int thismemno;
244 
245 	if(idp->idaddr->addrblock.vstg == STGCOMMON)
246 	{
247 		for(idp=current_BB->headid;idp;idp=idp->next)
248 			if(idp->idaddr->addrblock.vstg == STGCOMMON)
249 				killid(idp);
250 	}
251 	else if(idp->idaddr->addrblock.vstg == STGEQUIV)
252 	{
253 		thismemno=idp->idaddr->addrblock.memno;
254 		for(idp=current_BB->headid;idp;idp=idp->next)
255 			if(idp->idaddr->addrblock.vstg == STGEQUIV
256 			    && idp->idaddr->addrblock.memno == thismemno)
257 				killid(idp);
258 	}
259 	else killid(idp);
260 
261 }
262 
263 
264 
265 LOCAL appendnode(nodep)
266 valuen nodep;
267 /* Append a value node to all the IDblocks on that node's list of
268 ** dependent identifiers i.e., since this computation depends on
269 ** all the identifiers on its list then each of those identifiers should
270 ** include this node in their list of dependent nodes.
271 */
272 {
273 	register idlptr idl;
274 	register nodelptr nl;
275 
276 	for(idl=nodep->headdeplist;idl;idl=idl->next)
277 		if(idl->idp->idaddr->tag == TADDR ||
278 		   idl->idp->idaddr->tag == TTEMP)
279 			{
280 			nl=ALLOC(NODElist);
281 			nl->nodep = nodep;
282 			nl->next = idl->idp->headnodelist;
283 			idl->idp->headnodelist = nl;
284 			}
285 }
286 
287 
288 
289 LOCAL idlptr addadep(idp,nodep)
290 idptr idp;
291 valuen nodep;
292 /* Add an identifier to the dependents list of a value node.  Dependents
293 ** lists are ordered by increasing idp value
294 */
295 {
296 	register idlptr lp1,lp2;
297 
298 	lp2 = ALLOC(IDlist);
299 	lp2->idp = idp;
300 	if(nodep->headdeplist == 0) {
301 		lp2->next = 0;
302 		nodep->headdeplist = lp2;
303 	}
304 	else if(idp <= nodep->headdeplist->idp) {
305 		lp2->next = nodep->headdeplist;
306 		nodep->headdeplist = lp2;
307 	}
308 	else for(lp1 = nodep->headdeplist; lp1; lp1 = lp1->next)
309 		if( (lp1->next == 0) || (idp <= lp1->next->idp) )
310 		{
311 			lp2->next = lp1->next;
312 			lp1->next = lp2;
313 			break;
314 		}
315 	return(lp2);
316 }
317 
318 
319 
320 LOCAL valuen newnode(expr,left,right,rslt)
321 expptr expr;
322 valuen left,right,rslt;
323 /* Build a new value node
324 */
325 {
326 	register valuen p;
327 
328 	p= ALLOC(VALUEnode);
329 	p->opp = expr ;
330 	p->parent = NULL ;
331 	p->lc = left;
332 	p->rc = right;
333 	p->rs = rslt;
334 	p->n_dups = 0;
335 	p->is_dead = FALSE;
336 	p->next=NULL;
337 	p->headdeplist = mergedeps(left,right);
338 	p->headduplist=NULL;
339 	if(current_BB->headnode == 0) current_BB->headnode=p;
340 	else if(current_BB->tailnode) current_BB->tailnode->next=p;
341 	current_BB->tailnode=p;
342 
343 	return(p);
344 }
345 
346 
347 
348 LOCAL newid(idaddr,addrof_idptr)
349 expptr idaddr;
350 idptr *addrof_idptr;
351 /* Build a new IDblock and hook it on the current BB's ID list
352 */
353 {
354 	register idptr p;
355 
356 	p= ALLOC(IDblock);
357 
358 /* build a leaf value node for the identifier and put the ID on the leaf node's
359 ** list of dependent identifiers
360 */
361 	p->initval =  newnode(idaddr,NULL,NULL,NULL);
362 	p->initval->rs = p->initval;
363 	addadep(p,p->initval);
364 
365 	p->idaddr = idaddr;
366 	*addrof_idptr = p;
367 	p->headnodelist=NULL;
368 	p->next=NULL;
369 
370 }
371 
372 
373 
374 LOCAL addadup(parent,nodep)
375 expptr *parent;
376 valuen nodep;
377 
378 /* A subtree has been found that duplicates the calculation represented
379 ** by the value node referenced by nodep : add the root of the reduntant
380 ** tree to the value node's list of duplicates.
381 */
382 
383 {
384 	register duplptr dp;
385 	valuen child;
386 
387 	dp = ALLOC(DUPlist);
388 	dp->parent = parent;
389 	dp->next = nodep->headduplist;
390 	nodep->headduplist = dp;
391 	++nodep->n_dups;
392 
393 /* Check whether either of nodep's children is also a duplicate calculation
394 ** and if so peel off it's most recent dup record
395 */
396 
397 	if ( (child = nodep->lc) && (child->n_dups) )
398 	{
399 		dp = child->headduplist;
400 		child->headduplist = dp->next;
401 		free ( (charptr) dp );
402 		--child->n_dups;
403 	}
404 	if ( (child = nodep->rc) && (child->n_dups) )
405 	{
406 		dp = child->headduplist;
407 		child->headduplist = dp->next;
408 		free ( (charptr) dp );
409 		--child->n_dups;
410 	}
411 
412 }
413 
414 
415 
416 LOCAL samebase(ep1,ep2)
417 expptr ep1,ep2;
418 {
419     if ( ep1->tag == ep2->tag  )
420 	switch (ep2->tag) {
421 	    case TTEMP :
422 		if (ep1->tempblock.memalloc == ep2->tempblock.memalloc)
423 			return (TRUE);
424 		break;
425 	    case TADDR :
426 		if (ep1->addrblock.vstg == ep2->addrblock.vstg) {
427 		    switch(ep1->addrblock.vstg) {
428 			case STGEQUIV:
429 			case STGCOMMON:
430 			    if (ep1->addrblock.memno == ep2->addrblock.memno &&
431 				ISCONST(ep1->addrblock.memoffset) &&
432 				ISCONST(ep2->addrblock.memoffset) &&
433 				ep1->addrblock.memoffset->constblock.constant.ci ==
434 				ep2->addrblock.memoffset->constblock.constant.ci ) {
435 				    return(TRUE);
436 			    }
437 			    break;
438 
439 			default:
440 			    if (ep1->addrblock.memno == ep2->addrblock.memno ) {
441 				return(TRUE);
442 			    }
443 		    }
444 		}
445 		break;
446 	    case TCONST :
447 		if( (ep1->constblock.vtype) ==
448 		    (ep2->constblock.vtype)  )
449 		{
450 			union Constant *ap,*bp;
451 			ap= &ep1->constblock.constant;
452 			bp= &ep2->constblock.constant;
453 			switch(ep1->constblock.vtype)
454 
455 			{
456 			case TYSHORT:
457 			case TYLONG:
458 				if(ap->ci == bp->ci) return(TRUE);
459 				break;
460 			case TYREAL:
461 			case TYDREAL:
462 				if(ap->cd[0] == bp->cd[0]) return(TRUE);
463 				break;
464 			case TYCOMPLEX:
465 			case TYDCOMPLEX:
466 				if(ap->cd[0] == bp->cd[0] &&
467 				    ap->cd[1] == bp->cd[1] )
468 					return(TRUE);
469 				break;
470 			}
471 		}
472 		break;
473 
474 	    default :
475 		badtag ("samebase",ep2->tag);
476 	}
477     return(FALSE);
478 }
479 
480 
481 
482 LOCAL idptr findid(idaddr)
483 expptr idaddr;
484 
485 /* Find an identifier's IDblock given its idaddr. If the identifier has no
486 ** IBblock build one
487 */
488 
489 {
490 	register idptr idp;
491 	if(current_BB->headid == 0) newid(idaddr,&current_BB->headid);
492 	idp=current_BB->headid;
493 
494 	do {
495 		if (samebase(idp->idaddr,idaddr) )  break;
496 		if (idp->next == 0) {
497 			newid(idaddr,&idp->next);
498 			idp = idp->next;
499 			break;
500 		}
501 		idp = idp->next;
502 	}
503 	while(TRUE);
504 
505 	return(idp);
506 }
507 
508 
509 
510 LOCAL valuen findnode(ep,leftc,rightc)
511 expptr ep;
512 valuen leftc,rightc;
513 {
514 	/* Look for a matching value node in the available computations stack
515 	*/
516 	register valuen p;
517 
518 	for ( p=current_BB->headnode; p ; p=p->next)  {
519 		if( ( ! p->is_dead)   &&
520 		    (p->lc == leftc)  &&
521 		    (p->rc == rightc) &&
522 		    ( (ep->tag == TEXPR && p->opp->tag == TEXPR
523 		      && p->opp->exprblock.opcode == ep->exprblock.opcode
524 		      && p->opp->exprblock.vtype == ep->exprblock.vtype
525 		      )
526 		    || (ep->tag == TADDR) || (ep->tag == TTEMP)
527 		    )
528 		  )
529 			return(p);
530 	}
531 	return(NULL);
532 }
533 
534 
535 
536 LOCAL valuen scanchain(listp,p_parent)
537 expptr listp;
538 chainp *p_parent;
539 
540 /* Make value nodes from the chain hanging off a LISTBLOCK
541 */
542 
543 {
544 	valuen lnode,rnode,new,scantree();
545 	chainp p;
546 
547 	p= *p_parent;
548 	if (p == NULL) return(NULL);
549 	lnode = scantree( &p->datap);
550 	rnode = scanchain(listp, &p->nextp);
551 	new = newnode(listp,lnode,rnode,0);
552 	new->rs = new;
553 	return(new->rs);
554 }
555 
556 
557 
558 LOCAL valuen scantree(p_parent)
559 expptr *p_parent;
560 
561 /* build a value node and return its address. p must point to an
562 ** exprblock an addrblock a listblock  or a constblock.
563 */
564 
565 {
566 valuen lnode, rnode,rsltnode,new;
567 expptr opp,p;
568 Exprp ep1,ep2;
569 idptr idp;
570 
571 p = *p_parent;
572 if(p == NULL) return(NULL);
573 
574 switch (p->tag) {
575 	case TCONST :
576 		return( findid(p)->initval );
577 
578 	case TTEMP :
579 		idp = findid(p);
580 		if(idp->assgnval) return(idp->assgnval);
581 
582 		lnode = idp->initval;
583 		rnode = scantree( &p->tempblock.memalloc);
584 
585 		rsltnode = findnode(p,lnode,rnode);
586 		if(rsltnode)
587 			return(rsltnode);
588 		else {
589 			new = newnode(p,lnode,rnode,0);
590 			new->rs = new;
591 			new->parent = p_parent;
592 			return(new->rs);
593 		}
594 
595 	case TADDR :
596 		idp = findid(p);
597 		if(idp->assgnval) return(idp->assgnval);
598 
599 		lnode = idp->initval;
600 		rnode = scantree( &p->addrblock.memoffset);
601 
602 		rsltnode = findnode(p,lnode,rnode);
603 		if(rsltnode) {
604 #ifdef	notdef
605 			/*
606 			 * This code is broken until OPINDIRECT is implemented.
607 			 */
608 			if(p->addrblock.memoffset != NULL &&
609 			    p->addrblock.memoffset->tag == TEXPR)
610 				addadup(p_parent,rsltnode);
611 #endif	notdef
612 			return(rsltnode);
613 		}
614 		else {
615 			new = newnode(p,lnode,rnode,0);
616 			new->rs = new;
617 			new->parent = p_parent;
618 			return(new->rs);
619 		}
620 
621 	case TLIST :
622 		return(scanchain(p->listblock.listp,&p->listblock.listp));
623 
624 	default :
625 		badtag ("scantree",p->tag);
626 
627 	case TEXPR  :
628 		lnode = scantree(&p->exprblock.leftp);
629 		rnode = scantree(&p->exprblock.rightp);
630 
631 		switch (p->exprblock.opcode) {
632 			case OPASSIGN :
633 				{
634 				Addrp ap;
635 
636 				ap = (Addrp) p->exprblock.leftp;
637 				idp = findid(ap);
638 				killdepnodes(idp);
639 				if( ! ap->isarray ) {
640 					if(rnode->is_dead)idp->assgnval=idp->initval;
641 					else idp->assgnval = rnode;
642 				}
643 				new = newnode(p,idp->initval,NULL,NULL);
644 				appendnode(new);
645 				new->rs = new;
646 				return(new->rs);
647 				}
648 
649 			/*
650 			 * Don't optimize these...  they're a real hassle.
651 			 */
652 			case OPPLUSEQ :
653 			case OPSTAREQ :
654 				{
655 				Addrp ap;
656 
657 				ap = (Addrp) p->exprblock.leftp;
658 				idp = findid(ap);
659 				killdepnodes(idp);
660 				idp->assgnval = NULL;
661 				new = newnode(p,lnode,rnode,NULL);
662 				new->rs = new;
663 				return(new->rs);
664 				}
665 
666 			case OPCALL :
667 				{
668 				chainp cp;
669 
670 				if(p->exprblock.rightp)
671 
672 	/* pretend that all variables on the arglist have just
673 	** been assigned to i.e. kill of calculations that
674 	** depend on them. Not necessary for CCALL(by value)
675 	*/
676 
677 				for(cp=p->exprblock.rightp->listblock.listp;
678                                 cp;cp=cp->nextp)
679 					if (cp->datap->tag == TADDR ||
680 					    cp->datap->tag == TTEMP){
681 						idp = findid(cp->datap);
682 						killdepnodes(idp);
683 						idp->assgnval = NULL;
684 				}
685 
686 				new = newnode(p,lnode,rnode,NULL);
687 				new->rs = new;
688 				return(new->rs);
689 				}
690 
691 			case OPCONCAT:
692 			case OPADDR:
693 			case OPCOLON:
694 			case OPINDIRECT:
695 		/*
696 		 * For now, do not optimize LSHIFT until OPINDIRECT
697 		 * implemented.
698 		 */
699 			case OPLSHIFT:
700 				new = newnode(p,lnode,rnode,NULL);
701 				new->rs = new;
702 				return(new->rs);
703 
704 			case OPCOMMA:
705 				badop ("scantree",OPCOMMA);
706 				break;
707 
708 			default :
709 				rsltnode = findnode(p,lnode,rnode);
710 				if (rsltnode) {
711 					addadup(p_parent,rsltnode);
712 					return(rsltnode);
713 				}
714 				else {
715 					new = newnode(p,lnode,rnode,NULL);
716 					new->rs = new;
717 					new->parent = p_parent;
718 					appendnode(new);
719 					return(new->rs);
720 				}
721 			}
722 	}
723 }
724 
725 
726 
727 LOCAL prunetrees()
728 
729 /* The only optcse.c routine that does any real work: go through the available
730 ** computations stack and eliminate redundant subtrees.
731 */
732 
733 {
734 Addrp tempv;
735 register duplptr dl;
736 register valuen p;
737 expptr t;
738 int is_addrnode;
739 expptr *addr_tree1 = NULL ;
740 expptr tree2 = NULL ;
741 
742 for(p=current_BB->headnode;p;p=p->next)
743 {
744 	if(p->rs == NULL) {
745 		if( addr_tree1 && tree2 )
746 		     *addr_tree1 = fixtype(mkexpr(OPCOMMA,tree2,*addr_tree1));
747 		addr_tree1 = (expptr*) p->opp;
748 		tree2 = NULL;
749 	}
750 	if (p->n_dups ) {
751 
752 		if (p->opp->tag == TTEMP)
753 			fprintf(diagfile,"TTEMP in prunetrees - cbb\n");
754 		if(p->opp->tag == TADDR) is_addrnode = TRUE;
755 		else is_addrnode = FALSE;
756 
757 		if (is_addrnode)
758 			tempv = mktemp(TYADDR,NULL);
759 		else
760 			tempv = mktemp(p->opp->exprblock.vtype,
761 			    p->opp->exprblock.vleng);
762 		cse2count++;
763 
764 		if(tree2)
765 			tree2 = fixtype(mkexpr(OPCOMMA,tree2,
766 				fixtype(mkexpr(OPASSIGN,cpexpr(tempv),
767 				(is_addrnode ? addrof(p->opp) :  p->opp)
768 				))));
769 		else
770 			tree2 = fixtype(mkexpr(OPASSIGN,cpexpr(tempv),
771 				(is_addrnode ? addrof(p->opp) :  p->opp)
772 				));
773 
774 		if(is_addrnode)
775 			*(p->parent) = fixtype(mkexpr(OPINDIRECT,cpexpr(tempv), NULL));
776 		else
777 			*(p->parent) = (expptr) cpexpr(tempv);
778 
779 /* then replaces all future instances of the calculation by references to
780    the temporary */
781 
782 		for(dl=p->headduplist;dl->next;dl=dl->next) {
783 			cse1count++;
784 			frexpr(*dl->parent);
785 			if(is_addrnode)
786 				*(dl->parent) = fixtype(
787 					mkexpr(OPINDIRECT,cpexpr(tempv), NULL));
788 			else
789 				*(dl->parent) = (expptr) cpexpr(tempv);
790 		}
791 
792 /* the last reference does not use a copy since the temporary can
793    now be freed */
794 
795 		cse1count++;
796 		frexpr(*dl->parent);
797 		if(is_addrnode)
798 			*(dl->parent) = fixtype(mkexpr(OPINDIRECT,tempv, NULL));
799 		else
800 			*(dl->parent) = (expptr) tempv;
801 
802 		frtemp (tempv);
803 	}
804 }
805 if(addr_tree1 && tree2)
806 	*addr_tree1 = fixtype(mkexpr(OPCOMMA,tree2,*addr_tree1));
807 }
808 
809 
810 
811 LOCAL rewritebb (bb)
812 Bblockp bb;
813 {
814 	Slotp sp;
815 	expptr p;
816 
817 	if (bb == NULL)
818 		return;
819 	else
820 		current_BB = bb;
821 	sp = current_BB->first;
822 
823 	/* loop trough all BB slots and scan candidate expr trees when found */
824 
825 	for (sp = current_BB->first; ; sp = sp->next)
826 		{
827 		switch (sp->type)
828 		    {
829 		    case SKEQ :
830 		    case SKIFN :
831 		    case SKCMGOTO :
832 		    case SKCALL :
833 			newnode((expptr) &sp->expr,NULL,NULL,NULL);
834 			scantree(&sp->expr);
835 			break;
836 
837 		    default  :
838 			break;
839 		    }
840 		if (sp == current_BB->last) break;
841 		}
842 
843 /* use the information built up by scantree to prune reduntant subtrees */
844 	prunetrees();
845 
846 	current_BB = NULL;
847 }
848 
849 
850 
851 /*
852  *  removes all instances of OPCOMMA from the given subexpression of
853  *  the given buffer slot
854  */
855 
856 expptr rmcommaop (p,sl)
857 expptr	p;
858 Slotp	sl;
859 
860 {
861 expptr	leftp,rightp;
862 chainp	cp;
863 
864 if (!p)
865 	return (ENULL);
866 switch (p->tag)
867 	{
868 	case TEXPR:
869 		leftp = p->exprblock.leftp;
870 		rightp = p->exprblock.rightp;
871 		leftp = rmcommaop (leftp,sl);
872 		if (p->exprblock.opcode == OPCOMMA)
873 			{
874 			optinsert (SKEQ,leftp,0,0,sl);
875 			if (p->exprblock.vleng)
876 				free ((charptr) p->exprblock.vleng);
877 			free ((charptr) p);
878 			p = rmcommaop (rightp,sl);
879 			return (p);
880 			}
881 		p->exprblock.leftp = leftp;
882 		p->exprblock.rightp = rmcommaop (rightp,sl);
883 		return (p);
884 
885 	case TLIST:
886 		for (cp = p->listblock.listp; cp; cp = cp->nextp)
887 			cp->datap = (tagptr) rmcommaop (cp->datap,sl);
888 		return (p);
889 
890 	case TADDR:
891 		p->addrblock.memoffset = rmcommaop (p->addrblock.memoffset,sl);
892 		return (p);
893 
894 	default:
895 		return (p);
896 	}
897 }
898 
899 
900 
901 /*
902  *  scans the code buffer, performing common subexpression elimination
903  */
904 
905 optcse ()
906 
907 {
908 Slotp	sl;
909 Bblockp	bb;
910 
911 if (debugflag[13])
912 	return;
913 
914 cse1count = 0;
915 cse2count = 0;
916 for (sl = firstslot; sl; sl = sl->next)
917 	sl->expr = rmcommaop (sl->expr,sl);
918 for (bb = firstblock; bb; bb = bb->next)
919 	rewritebb (bb);
920 
921 if (debugflag[0])
922 	fprintf (diagfile,
923 		"%d common subexpression use%s eliminated (%d definition%s)\n",
924 		cse1count, (cse1count==1 ? "" : "s"),
925 		cse2count, (cse2count==1 ? "" : "s"));
926 }
927