New Memory Allocation functions
[fw/sdcc] / src / SDCCloop.c
1 /*-------------------------------------------------------------------------
2
3   SDCCloop.c - source file for loop detection & optimizations
4
5              Written By -  Sandeep Dutta . sandeep.dutta@usa.net (1998)
6
7    This program is free software; you can redistribute it and/or modify it
8    under the terms of the GNU General Public License as published by the
9    Free Software Foundation; either version 2, or (at your option) any
10    later version.
11    
12    This program is distributed in the hope that it will be useful,
13    but WITHOUT ANY WARRANTY; without even the implied warranty of
14    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15    GNU General Public License for more details.
16    
17    You should have received a copy of the GNU General Public License
18    along with this program; if not, write to the Free Software
19    Foundation, 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
20    
21    In other words, you are welcome to use, share and improve this program.
22    You are forbidden to forbid anyone else to use, share and improve
23    what you give them.   Help stamp out software-hoarding!  
24 -------------------------------------------------------------------------*/
25
26 #include "common.h"
27 #include "newalloc.h"
28
29 DEFSETFUNC(isDefAlive);
30
31 STACK_DCL(regionStack,eBBlock *, MAX_NEST_LEVEL * 10);
32
33 /*-----------------------------------------------------------------*/
34 /* newInduction - creates a new induction variable                 */
35 /*-----------------------------------------------------------------*/
36 induction *newInduction (operand *sym, unsigned int op, 
37                          long constVal, iCode *ic, operand *asym)
38 {
39     induction *ip;
40
41     ip = Safe_calloc(sizeof(induction));
42
43     ip->sym = sym;
44     ip->asym= asym;
45     ip->op = op;
46     ip->cval = constVal;   
47     ip->ic = ic;
48
49     return ip;
50 }
51
52 /*-----------------------------------------------------------------*/
53 /* newRegion - allocate & returns a loop structure                 */
54 /*-----------------------------------------------------------------*/
55 region *newRegion ()
56 {
57     region *lp ;
58
59     lp = Safe_calloc(sizeof(region));  
60
61     return lp;
62 }
63
64
65 /*-----------------------------------------------------------------*/
66 /* pinduction - prints induction                                   */
67 /*-----------------------------------------------------------------*/
68 DEFSETFUNC(pinduction)
69 {
70     induction *ip = item;
71     iCodeTable *icTab;
72
73     fprintf(stdout,"\t");
74     printOperand(ip->sym,stdout);
75     icTab = getTableEntry(ip->ic->op);
76     icTab->iCodePrint(stdout,ip->ic,icTab->printName);
77     fprintf(stdout," %04d\n",(int)ip->cval);
78     return 0;
79 }
80
81 /*-----------------------------------------------------------------*/
82 /* pregion - prints loop information                                */
83 /*-----------------------------------------------------------------*/
84 DEFSETFUNC(pregion)
85 {
86     region *lp = item;
87
88     printf("================\n");
89     printf(" loop with entry -- > "); printEntryLabel(lp->entry,ap);
90     printf("\n");
91     printf(" loop body --> "); applyToSet(lp->regBlocks,printEntryLabel);
92     printf("\n");
93     printf(" loop exits --> "); applyToSet(lp->exits,printEntryLabel);
94     printf("\n");
95     return 0;
96 }
97
98 /*-----------------------------------------------------------------*/
99 /* backEdges - returns a list of back edges                        */
100 /*-----------------------------------------------------------------*/
101 DEFSETFUNC(backEdges)
102 {
103     edge *ep = item;
104     V_ARG(set **,bEdges);
105
106     /* if this is a back edge ; to determine this we check */
107     /* to see if the 'to' is in the dominator list of the  */
108     /* 'from' if yes then this is a back edge              */
109     if (bitVectBitValue (ep->from->domVect,ep->to->bbnum)) {
110         addSetHead (bEdges,ep);
111         return 1;
112     }
113
114     return 0;
115 }
116
117 /*-----------------------------------------------------------------*/
118 /* intersectLoopSucc - returns intersection of loop Successors     */
119 /*-----------------------------------------------------------------*/
120 static bitVect *intersectLoopSucc ( set *lexits, eBBlock **ebbs)
121 {    
122     bitVect *succVect = NULL;    
123     eBBlock *exit = setFirstItem(lexits);
124     
125     if (!exit)
126         return NULL;
127
128     succVect = bitVectCopy(exit->succVect);
129
130     for (exit = setNextItem(lexits); exit ; 
131          exit = setNextItem(lexits)) {
132         succVect = bitVectIntersect(succVect,
133                                  exit->succVect);                               
134     }
135     
136     return succVect ;
137 }
138
139
140 /*-----------------------------------------------------------------*/
141 /* loopInsert will insert a block into the loop set                */
142 /*-----------------------------------------------------------------*/
143 static void loopInsert (set **regionSet, eBBlock *block)
144 {
145     if (!isinSet (*regionSet,block)) {
146         addSetHead (regionSet,block);
147         STACK_PUSH(regionStack,block);
148     }
149 }
150
151 /*-----------------------------------------------------------------*/
152 /* insertIntoLoop - insert item into loop                          */
153 /*-----------------------------------------------------------------*/
154 DEFSETFUNC(insertIntoLoop)
155 {
156     eBBlock *ebp = item ;
157     V_ARG(set **,regionSet);
158     
159     loopInsert (regionSet,ebp);
160     return 0;
161 }
162
163 /*-----------------------------------------------------------------*/
164 /* isNotInBlocks - will return 1 if not is blocks                  */
165 /*-----------------------------------------------------------------*/
166 DEFSETFUNC(isNotInBlocks)
167 {
168     eBBlock *ebp = item;
169     V_ARG(set *,blocks);    
170
171     if (! isinSet (blocks,ebp))                 
172         return 1;    
173
174     return 0;   
175 }
176
177 /*-----------------------------------------------------------------*/
178 /* hasIncomingDefs - has definitions coming into the loop. i.e.    */
179 /* check to see if the preheaders outDefs has any definitions      */
180 /*-----------------------------------------------------------------*/
181 int hasIncomingDefs (region *lreg, operand *op)
182 {
183     eBBlock *preHdr = lreg->entry->preHeader;
184
185     if (preHdr && bitVectBitsInCommon(preHdr->outDefs,OP_DEFS(op)))
186         return 1;
187     return 0;
188 }
189
190 /*-----------------------------------------------------------------*/
191 /* findLoopEndSeq - will return the sequence number of the last    */
192 /* iCode with the maximum dfNumber in the region                   */
193 /*-----------------------------------------------------------------*/
194 int findLoopEndSeq (region *lreg)
195 {
196     eBBlock *block;
197     eBBlock *lblock;
198
199     for (block = lblock =setFirstItem(lreg->regBlocks); block;
200          block = setNextItem(lreg->regBlocks)) {
201         if (block != lblock && block->lSeq > lblock->lSeq)
202             lblock = block;
203     }
204
205     return lblock->lSeq;
206 }
207
208 /*-----------------------------------------------------------------*/
209 /* addToExitsMarkDepth - will add the the exitSet all blocks that  */
210 /* have exits, will also update the depth field in the blocks      */
211 /*-----------------------------------------------------------------*/
212 DEFSETFUNC(addToExitsMarkDepth)
213 {
214     eBBlock *ebp = item ;
215     V_ARG(set *,loopBlocks);
216     V_ARG(set **,exits);    
217     V_ARG(int, depth);
218     V_ARG(region *,lr);
219
220     /* mark the loop depth of this block */
221     if (!ebp->depth)
222         ebp->depth = depth;
223
224     /* put the loop region info in the block */
225     /* NOTE: here we will update only the inner most loop
226        that it is a part of */
227     if (!ebp->partOfLoop)
228         ebp->partOfLoop = lr;
229
230     /* if any of the successors go out of the loop then */
231     /* we add this one to the exits */
232     if ( applyToSet(ebp->succList,isNotInBlocks,loopBlocks)) {
233         addSetHead (exits,ebp);
234         return 1;
235     }
236    
237     return 0;
238 }
239
240 /*-----------------------------------------------------------------*/
241 /* createLoop - will create a set of region                        */
242 /*-----------------------------------------------------------------*/
243 DEFSETFUNC(createLoop)
244 {
245     edge *ep = item;
246     V_ARG(set **,allRegion);
247     region *aloop = newRegion();
248     eBBlock *block;
249
250     /* make sure regionStack is empty */
251     while (!STACK_EMPTY(regionStack))
252         STACK_POP(regionStack);
253
254     /* add the entryBlock */
255     addSet (&aloop->regBlocks,ep->to);
256     loopInsert (&aloop->regBlocks,ep->from);
257
258     while (!STACK_EMPTY(regionStack)) {
259         block = STACK_POP(regionStack);
260         /* if block != entry */
261         if (block != ep->to)
262             applyToSet(block->predList,insertIntoLoop,&aloop->regBlocks);
263     }
264
265     aloop->entry = ep->to ;
266        
267     /* now add it to the set */
268     addSetHead (allRegion,aloop);
269     return 0;
270 }
271
272 /*-----------------------------------------------------------------*/
273 /* dominatedBy - will return 1 if item is dominated by block       */
274 /*-----------------------------------------------------------------*/
275 DEFSETFUNC(dominatedBy) 
276 {
277     eBBlock *ebp = item;
278     V_ARG(eBBlock *,block);
279
280     return bitVectBitValue (ebp->domVect,block->bbnum);
281 }
282
283 /*-----------------------------------------------------------------*/
284 /* addDefInExprs - adds an expression into the inexpressions       */
285 /*-----------------------------------------------------------------*/
286 DEFSETFUNC(addDefInExprs)
287 {
288     eBBlock *ebp = item;
289     V_ARG(cseDef *,cdp);
290     V_ARG(eBBlock **,ebbs);
291     V_ARG(int,count);
292
293     addSetHead(&ebp->inExprs,cdp);
294     cseBBlock (ebp,0,ebbs,count);
295     return 0;
296 }
297
298 /*-----------------------------------------------------------------*/
299 /* assignmentsToSym - for a set of blocks determine # time assigned*/
300 /*-----------------------------------------------------------------*/
301  int assignmentsToSym (set *sset, operand *sym)
302 {   
303     eBBlock *ebp ;
304     int assigns = 0;
305     set *blocks = setFromSet(sset);
306
307     for (ebp = setFirstItem(blocks) ; ebp ;
308          ebp = setNextItem(blocks)) {       
309         
310         /* get all the definitions for this symbol
311            in this block */
312         bitVect *defs = bitVectIntersect(ebp->ldefs,OP_DEFS(sym));
313         assigns += bitVectnBitsOn(defs);
314         setToNull((void **)&defs);
315         
316     }
317
318     return assigns;
319 }
320
321
322 /*-----------------------------------------------------------------*/
323 /* isOperandInvariant - determines if an operand is an invariant   */
324 /*-----------------------------------------------------------------*/
325 int isOperandInvariant (operand *op, region *theLoop, set *lInvars)
326 {
327     int opin = 0 ;
328     /* operand is an invariant if it is a                */
329     /*       a. constants .                              */
330     /*       b. that have defintions reaching loop entry */
331     /*       c. that are already defined as invariant    */
332     /*       d. has no assignments in the loop           */    
333     if (op) {
334         if (IS_OP_LITERAL(op))
335             opin = 1 ;
336         else
337             if (IS_SYMOP(op) &&
338                 OP_SYMBOL(op)->addrtaken)
339                 opin = 0 ;
340             else
341                 if (ifDefSymIs(theLoop->entry->inExprs,op))
342                     opin = 1 ;
343                 else
344                     if (ifDefSymIs(lInvars,op))
345                         opin = 1 ;              
346                     else
347                         if (IS_SYMOP(op)         &&
348                             ! IS_OP_GLOBAL(op)   &&
349                             ! IS_OP_VOLATILE(op) &&                             
350                             assignmentsToSym (theLoop->regBlocks,op) == 0 )
351                             opin = 1 ;              
352     } else opin++ ;
353
354     return opin ;
355 }
356
357 /*-----------------------------------------------------------------*/
358 /* pointerAssigned - will return 1 if pointer set found            */
359 /*-----------------------------------------------------------------*/
360 DEFSETFUNC(pointerAssigned)
361 {
362     eBBlock *ebp = item;
363     V_ARG(operand *,op);
364
365     return ebp->hasFcall || bitVectBitValue(ebp->ptrsSet,op->key);
366 }
367
368 /*-----------------------------------------------------------------*/
369 /* hasNonPtrUse - returns true if operand has non pointer usage    */
370 /*-----------------------------------------------------------------*/
371 DEFSETFUNC(hasNonPtrUse)
372 {
373     eBBlock *ebp = item;
374     V_ARG(operand *,op);
375     iCode *ic = usedInRemaining(op,ebp->sch);
376
377     if (ic && !POINTER_SET(ic) && !POINTER_GET(ic))
378         return 1;
379
380     return 0;
381     
382 }
383
384 /*-----------------------------------------------------------------*/
385 /* loopInvariants - takes loop invariants out of region            */
386 /*-----------------------------------------------------------------*/
387  int loopInvariants( region *theLoop , eBBlock **ebbs, int count)
388 {      
389     eBBlock *lBlock ;
390     set *lInvars = NULL ;
391     
392     int change = 0 ;
393
394     /* if the preHeader does not exist then do nothing */
395     /* or no exits then do nothing ( have to think about this situation */
396     if (theLoop->entry->preHeader == NULL ||
397         theLoop->exits == NULL )
398         return 0;
399
400     /* we will do the elimination for those blocks        */
401     /* in the loop that dominates all exits from the loop */
402     for (lBlock = setFirstItem(theLoop->regBlocks); lBlock;
403          lBlock = setNextItem(theLoop->regBlocks)) {
404         
405         iCode *ic;
406         int domsAllExits ;
407         int i ;
408
409         /* mark the dominates all exits flag */
410         domsAllExits = ( applyToSet (theLoop->exits,dominatedBy,lBlock) ==
411                          elementsInSet (theLoop->exits));
412         
413
414         /* now we go thru the instructions of this block and */
415         /* collect those instructions with invariant operands*/
416         for ( ic = lBlock->sch ; ic ; ic = ic->next ) {
417             
418             int lin , rin ;
419             cseDef *ivar ;
420
421             if (SKIP_IC(ic) || POINTER_SET(ic) || ic->op == IFX)
422                 continue ;
423
424             /* if result is volatile then skip */
425             if (IC_RESULT(ic) &&  
426                 ( isOperandVolatile(IC_RESULT(ic),TRUE) || 
427                   IS_OP_PARM(IC_RESULT(ic))))
428                 continue ;
429
430             lin = rin = 0 ;
431             
432             /* special case */
433             /* if address of then it is an invariant */
434             if (ic->op == ADDRESS_OF && 
435                 IS_SYMOP(IC_LEFT(ic)) &&
436                 IS_AGGREGATE(operandType(IC_LEFT(ic))))
437                 lin++;  
438             else
439                 /* check if left operand is an invariant */
440                 if ( (lin = isOperandInvariant (IC_LEFT(ic),theLoop,lInvars)))  
441                     /* if this is a pointer get then make sure
442                        that the pointer set does not exist in 
443                        any of the blocks */
444                     if (POINTER_GET(ic) && 
445                         ( applyToSet (theLoop->regBlocks,pointerAssigned,IC_LEFT(ic)) ))
446                         lin = 0;                                    
447
448             /* do the same for right */
449             rin = isOperandInvariant (IC_RIGHT(ic),theLoop, lInvars);       
450
451             /* if this is a POINTER_GET then special case, make sure all
452                usages within the loop are POINTER_GET any other usage
453                would mean that this is not an invariant , since the pointer
454                could then be passed as a parameter */
455             if (POINTER_GET(ic) &&
456                 applyToSet(theLoop->regBlocks,hasNonPtrUse,IC_LEFT(ic)))
457                 continue ;
458
459             /* if both the left & right are invariants : then check that*/
460             /* this definition exists in the out definition of all the  */
461             /* blocks, this will ensure that this is not assigned any   */
462             /* other value in the loop , and not used in this block     */
463             /* prior to this definition which means only this definition*/
464             /* is used in this loop                                     */
465             if (lin && rin && IC_RESULT(ic)) {
466                 eBBlock *sBlock ;
467                 set *lSet = setFromSet(theLoop->regBlocks);
468
469                 /* if this block does not dominate all exists */
470                 /* make sure this defintion is not used anywhere else */
471                 if (!domsAllExits) {
472
473                     if (isOperandGlobal(IC_RESULT(ic)))
474                         continue;
475                     /* for successors for all exits */
476                     for ( sBlock = setFirstItem(theLoop->exits); sBlock; 
477                           sBlock = setNextItem(theLoop->exits)) {
478                         
479                         for(i=0; i < count; ebbs[i++]->visited = 0);
480                         lBlock->visited = 1;
481                         if ( applyToSet (sBlock->succList,isDefAlive,ic))
482                             break ;
483                     }
484
485                     /* we have found usage */
486                     if (sBlock )
487                         continue ;
488                 }
489                 
490                 /* now make sure this is the only definition */
491                 for (sBlock = setFirstItem(lSet); sBlock ;
492                      sBlock = setNextItem (lSet)) {
493                     /* if this is the block make sure the definition */
494                     /* reaches the end of the block */
495                     if (sBlock == lBlock ) {
496                         if (! ifDiCodeIs (sBlock->outExprs,ic))
497                             break;
498                     }
499                     else
500                         if (bitVectBitsInCommon (sBlock->defSet,OP_DEFS(IC_RESULT(ic))))
501                             break;
502                 }
503                 
504                 if (sBlock)
505                     continue ; /* another definition present in the block */
506
507                 /* now check if it exists in the in of this block */
508                 /* if not then it was killed before this instruction */
509                 if (! bitVectBitValue (lBlock->inDefs,ic->key))
510                     continue ;
511
512                 /* now we know it is a true invariant */
513                 /* remove it from the insts chain & put */
514                 /* in the invariant set                */
515                 OP_SYMBOL(IC_RESULT(ic))->isinvariant = 1;
516                 remiCodeFromeBBlock (lBlock,ic);
517                 
518                 /* maintain the data flow */
519                 /* this means removing from definition from the */
520                 /* defset of this block and adding it to the    */
521                 /* inexpressions of all blocks within the loop  */
522                 bitVectUnSetBit (lBlock->defSet,ic->key);
523                 bitVectUnSetBit (lBlock->ldefs,ic->key);
524                 ivar = newCseDef(IC_RESULT(ic),ic);
525                 applyToSet (theLoop->regBlocks, addDefInExprs, ivar,ebbs,count);
526                 addSet(&lInvars,ivar);
527             }
528         }
529     } /* for all loop blocks */
530
531     /* if we have some invariants then */
532     if (lInvars) {
533         eBBlock *preHdr= theLoop->entry->preHeader ;
534         iCode *icFirst = NULL , *icLast = NULL ;
535         cseDef *cdp;
536
537         /* create an iCode chain from it */
538         for (cdp = setFirstItem(lInvars); cdp ; cdp = setNextItem(lInvars)) {
539
540             /* maintain data flow .. add it to the */
541             /* ldefs defSet & outExprs of the preheader  */
542             preHdr->defSet = bitVectSetBit (preHdr->defSet,cdp->diCode->key);
543             preHdr->ldefs = bitVectSetBit (preHdr->ldefs,cdp->diCode->key);
544             cdp->diCode->lineno = preHdr->ech->lineno;
545             addSetHead (&preHdr->outExprs,cdp);
546             
547
548             if (!icFirst)
549                 icFirst = cdp->diCode;
550             if (icLast) {
551                 icLast->next = cdp->diCode;
552                 cdp->diCode->prev = icLast;
553                 icLast = cdp->diCode ;
554             } else 
555                 icLast = cdp->diCode;   
556             change++ ;
557         }
558        
559         /* add the instruction chain to the end of the 
560            preheader for this loop, preheaders will always
561            have atleast a label */
562         preHdr->ech->next = icFirst ;
563         icFirst->prev = preHdr->ech ;
564         preHdr->ech = icLast;
565         icLast->next = NULL;
566         
567     }
568     return change ;
569 }
570
571 /*-----------------------------------------------------------------*/
572 /* addressTaken - returns true if the symbol is found in the addrof*/
573 /*-----------------------------------------------------------------*/
574 int addressTaken (set *sset ,operand *sym)
575 {
576     set *loop;
577     eBBlock *ebp ;
578     set *loop2;   
579
580     for (loop = sset; loop ; loop = loop->next) {
581         ebp = loop->item;
582         loop2 = ebp->addrOf ;
583         while (loop2) {
584             if (isOperandEqual((operand *)loop2->item,sym))
585                 return 1;
586             loop2 = loop2->next;
587         }
588     }
589
590     return 0;
591 }
592
593
594 /*-----------------------------------------------------------------*/
595 /* findInduction :- returns 1 & the item if the induction is found */
596 /*-----------------------------------------------------------------*/
597 DEFSETFUNC(findInduction)
598 {
599     induction *ip = item;
600     V_ARG(operand *,sym);
601     V_ARG(induction **,ipp);
602
603     if (isOperandEqual(ip->sym,sym)) {
604         *ipp = ip;
605         return 1;
606     }
607
608     return 0;
609 }
610
611 /*-----------------------------------------------------------------*/
612 /* findDefInRegion - finds the definition within the region        */
613 /*-----------------------------------------------------------------*/
614 iCode *findDefInRegion (set *regBlocks, operand *defOp, eBBlock **owner)
615 {
616     eBBlock *lBlock ;
617     
618     /* for all blocks in the region */
619     for (lBlock = setFirstItem(regBlocks); lBlock ;
620          lBlock = setNextItem(regBlocks)) {
621
622         /* if a definition for this exists */
623         if (bitVectBitsInCommon(lBlock->defSet,OP_DEFS(defOp))) {
624             iCode *ic;
625
626             /* go thru the instruction chain to find it */
627             for (ic = lBlock->sch ; ic ; ic = ic->next )                
628                 if (bitVectBitValue (OP_DEFS(defOp),ic->key)) {
629                     if (owner)
630                         *owner = lBlock ;
631                     return ic;
632                 }
633         }
634     }
635
636     return NULL ;
637 }
638
639 /*-----------------------------------------------------------------*/
640 /* basicInduction - finds the basic induction variables in a loop  */
641 /*-----------------------------------------------------------------*/
642 set *basicInduction (region *loopReg , eBBlock **ebbs, int count)
643 {
644     eBBlock *lBlock ;
645     set *indVars = NULL ;
646
647     /* i.e. all assignments of the form a := a +/- const*/
648     /* for all blocks within the loop do */
649     for ( lBlock = setFirstItem(loopReg->regBlocks); lBlock ;
650           lBlock = setNextItem(loopReg->regBlocks)) {
651         
652         iCode *ic, *dic ;
653
654         /* for all instructions in the blocks do */
655         for ( ic = lBlock->sch ; ic ; ic = ic->next ) {
656             
657             operand *aSym ;
658             unsigned long litValue ;
659             induction *ip;
660             iCode *indIc;
661             eBBlock *owner = NULL;
662             int nexits;
663
664             /* look for assignments of the form */
665             /*   symbolVar := iTempNN */
666             if ( ic->op != '=')
667                 continue ;
668
669             if (!IS_TRUE_SYMOP(IC_RESULT(ic)) &&
670                 !OP_SYMBOL(IC_RESULT(ic))->isreqv)
671                 continue ;
672
673             if (isOperandGlobal(IC_RESULT(ic)))
674                 continue ;
675
676             if (!IS_ITEMP(IC_RIGHT(ic)))
677                 continue ;
678
679             /* if it has multiple assignments within the loop then skip */
680             if (assignmentsToSym (loopReg->regBlocks,IC_RESULT(ic)) > 1 )
681                 continue ;
682             
683             /* if the address of this was taken inside the loop then continue */
684             if (addressTaken (loopReg->regBlocks,IC_RESULT(ic)))
685                 continue ;
686
687             /* find the definition for the result in the block */
688             if (! (dic = findDefInRegion (setFromSet(loopReg->regBlocks),
689                                           IC_RIGHT(ic),&owner)))
690                 continue ;
691
692             /* if not +/- continue */
693             if (dic->op != '+' && dic->op != '-')
694                 continue ;
695
696             /* make sure definition is of the form  a +/- c */
697             if (!IS_OP_LITERAL(IC_LEFT(dic)) && !IS_OP_LITERAL(IC_RIGHT(dic)))
698                 continue ;
699             
700             aSym = (IS_OP_LITERAL(IC_RIGHT(dic)) ? 
701                     (litValue = operandLitValue(IC_RIGHT(dic)),IC_LEFT(dic)) : 
702                     (litValue = operandLitValue(IC_LEFT(dic)),IC_RIGHT(dic)));
703             
704             if (!isOperandEqual(IC_RESULT(ic),aSym) &&
705                 !isOperandEqual(IC_RIGHT(ic),aSym)) {
706                 iCode *ddic ;
707                 /* find the definition for this and check */
708                 if (!(ddic = findDefInRegion (setFromSet(loopReg->regBlocks),
709                                               aSym,&owner)))                
710                     continue ;
711
712                 if (ddic->op != '=')
713                     continue ;
714
715                 if (!isOperandEqual(IC_RESULT(ddic),aSym) ||
716                     !isOperandEqual(IC_RIGHT(ddic),IC_RESULT(ic)))
717                     continue ;
718             }
719
720             /* if the right hand side has more than one usage then
721                don't make it an induction (will have to think some more) */
722             if (bitVectnBitsOn(OP_USES(IC_RIGHT(ic))) > 1)
723                     continue;
724
725             /* if the definition is volatile then it cannot be
726                an induction object */
727             if (isOperandVolatile(IC_RIGHT(ic),FALSE) ||
728                 isOperandVolatile(IC_RESULT(ic),FALSE))
729                 continue;
730
731             /* whew !! that was a lot of work to find the definition */
732             /* create an induction object */
733             indIc = newiCode('=',NULL,IC_RESULT(ic));
734             indIc->lineno = ic->lineno;
735             IC_RESULT(indIc) = operandFromOperand(IC_RIGHT(ic));
736             IC_RESULT(indIc)->isaddr = 0;
737             OP_SYMBOL(IC_RESULT(indIc))->isind = 1;
738             ip = newInduction (IC_RIGHT(ic),dic->op,litValue,indIc,NULL);
739             
740             /* replace the inducted variable by the iTemp */
741             replaceSymBySym (loopReg->regBlocks,IC_RESULT(ic),IC_RIGHT(ic));
742
743             /* if it has only one exit then remove it from here
744                and put it in the exit block */
745             nexits = elementsInSet (loopReg->exits);
746             if (nexits == 1) {
747                 eBBlock *exit = setFirstItem(loopReg->exits);
748
749                 /* if it is the same block then there is no
750                    need to move it about */
751                 if ( exit != lBlock) {
752                     iCode *saveic = ic->prev;
753                     /* remove it */
754                     remiCodeFromeBBlock(lBlock,ic);
755                     /* clear the definition */
756                     bitVectUnSetBit(lBlock->defSet,ic->key);
757                     /* add it to the exit */
758                     addiCodeToeBBlock(exit,ic,NULL);
759                     /* set the definition bit */
760                     exit->defSet = bitVectSetBit(exit->defSet,ic->key);
761                     ic = saveic ;
762                 }
763             }
764             
765             /* if the number of exits is greater than one then
766                we use another trick ; we will create an intersection
767                of succesors of the exits, then take those that are not
768                part of the loop and have dfNumber greater loop entry
769                and insert a new definition in them */
770             if ( nexits > 1) {
771
772                 bitVect *loopSuccs = intersectLoopSucc (loopReg->exits,ebbs);
773                 
774                 /* loopSuccs now contains intersection
775                    of all the loops successors */
776                 if (loopSuccs) {
777                     int i;
778                     for (i = 0 ; i < loopSuccs->size; i++) {
779                         if (bitVectBitValue(loopSuccs,i)) {
780
781                             eBBlock *eblock = ebbs[i];
782                             
783                             /* if the successor does not belong to the loop
784                                and will be executed after the loop : then
785                                add a definition to the block */
786                             if ( !isinSet(loopReg->regBlocks,eblock) &&
787                                  eblock->dfnum > loopReg->entry->dfnum) {
788                                 /* create the definition */
789                                 iCode *newic = newiCode('=',NULL,
790                                                         operandFromOperand(IC_RIGHT(ic)));
791                                 IC_RESULT(newic) = operandFromOperand(IC_RESULT(ic));
792                                 OP_DEFS(IC_RESULT(newic)) = 
793                                     bitVectSetBit(OP_DEFS(IC_RESULT(newic)),newic->key);
794                                 OP_USES(IC_RIGHT(newic)) = 
795                                     bitVectSetBit(OP_USES(IC_RIGHT(newic)),newic->key);
796                                 /* and add it */
797                                 if (eblock->sch && eblock->sch->op == LABEL)
798                                     addiCodeToeBBlock(eblock,newic,eblock->sch->next);
799                                 else
800                                     addiCodeToeBBlock(eblock,newic,eblock->sch);
801                                 /* set the definition bit */
802                                 eblock->defSet = bitVectSetBit(eblock->defSet,ic->key); 
803                             }
804                         }
805                     }
806                 }
807             }
808                
809             addSet (&indVars,ip);
810         }
811
812     } /* end of all blocks for basic induction variables */
813     
814     return indVars;
815 }
816     
817 /*-----------------------------------------------------------------*/
818 /* loopInduction - remove induction variables from a loop          */
819 /*-----------------------------------------------------------------*/
820  int loopInduction( region *loopReg, eBBlock **ebbs, int count)
821 {   
822     int change = 0 ;
823     eBBlock *lBlock, *lastBlock = NULL;
824     set *indVars = NULL ;
825     set *basicInd=NULL ;
826
827     if (loopReg->entry->preHeader == NULL)
828         return 0;
829
830     /* we first determine the basic Induction variables */
831     basicInd = setFromSet(indVars = basicInduction(loopReg, ebbs,count));
832
833     /* find other induction variables : by other we mean definitions of */
834     /* the form x := y (* | / ) <constant> .. we will move  this one to */
835     /* beginning of the loop and reduce strength i.e. replace with +/-  */
836     /* these expensive expressions: OH! and y must be induction too     */
837     for ( lBlock = setFirstItem(loopReg->regBlocks), lastBlock = lBlock; 
838           lBlock && indVars;
839           lBlock = setNextItem(loopReg->regBlocks)) {
840         
841         iCode *ic, *indIc;
842         induction *ip;
843
844         /* last block is the one with the highest block 
845            number */
846         if (lastBlock->bbnum < lBlock->bbnum )
847             lastBlock = lBlock;
848
849         for ( ic = lBlock->sch ; ic ; ic = ic->next ) {
850             operand *aSym ;       
851             unsigned long litVal ;
852             int lr = 0;
853
854             /* consider only * & / */
855             if (ic->op != '*' && ic->op != '/')
856                 continue ;
857
858             /* if the result has more definitions then */
859             if (assignmentsToSym(loopReg->regBlocks,IC_RESULT(ic)) > 1)
860                 continue ;
861
862             /* check if the operands are what we want */
863             /* i.e. one of them an symbol the other a literal */
864             if (! ( (IS_SYMOP(IC_LEFT(ic)) && IS_OP_LITERAL(IC_RIGHT(ic))) ||
865                     (IS_OP_LITERAL(IC_LEFT(ic)) && IS_SYMOP(IC_RIGHT(ic))) ))
866                 continue ;
867
868             aSym = (IS_SYMOP(IC_LEFT(ic)) ? 
869                     (lr = 1, litVal = operandLitValue(IC_RIGHT(ic)), IC_LEFT(ic) ) : 
870                     (litVal= operandLitValue(IC_LEFT(ic)), IC_RIGHT(ic) ) ) ;     
871
872             ip = NULL ;
873             /* check if this is an induction variable */
874             if (! applyToSetFTrue (basicInd,findInduction,aSym,&ip))
875                 continue ;                  
876             
877             /* ask port for size not worth if native instruction
878                exist for multiply & divide */
879             if (getSize(operandType(IC_LEFT(ic))) <= port->muldiv.native_below ||
880                 getSize(operandType(IC_RIGHT(ic))) <= port->muldiv.native_below)
881                 continue;
882
883             /* if this is a division then the remainder should be zero 
884                for it to be inducted */
885             if (ic->op == '/' && (ip->cval % litVal))
886                 continue ;
887
888             /* create the iCode to be placed in the loop header */
889             /* and create the induction object */
890             
891             /* create an instruction */
892             /* this will be put on the loop header */
893             indIc = newiCode(ic->op,
894                              operandFromOperand(aSym),
895                              operandFromLit(litVal));
896             indIc->lineno = ic->lineno;
897             IC_RESULT(indIc) = operandFromOperand(IC_RESULT(ic));
898             OP_SYMBOL(IC_RESULT(indIc))->isind = 1;
899
900             /* keep track of the inductions */
901             litVal = (ic->op == '*' ? (litVal * ip->cval) :
902                       (ip->cval / litVal));         
903
904             addSet (&indVars,
905                     newInduction (IC_RESULT(ic),ip->op,litVal,indIc,NULL)); 
906
907             /* now change this instruction */
908             ic->op = ip->op;
909             if (lr) {
910                 IC_LEFT(ic) = operandFromOperand(IC_RESULT(ic));
911                 IC_RIGHT(ic) = operandFromLit(litVal);
912             } else {
913                 IC_RIGHT(ic) = operandFromOperand(IC_RESULT(ic));
914                 IC_LEFT(ic) = operandFromLit(litVal);
915             }
916             
917             /* we need somemore initialisation code */
918             /* we subtract the litVal from itself if increment */
919             if ( ic->op == '+' ) {
920                 indIc = newiCode('-',
921                                  operandFromOperand(IC_RESULT(ic)),
922                                  operandFromLit(litVal));
923                 indIc->lineno = ic->lineno;
924                 IC_RESULT(indIc) = operandFromOperand(IC_RESULT(ic));
925                 
926                 addSet (&indVars,
927                         newInduction (IC_RESULT(ic),ip->op,litVal,indIc,NULL)); 
928             }
929         }
930     }    
931
932     /* if we have some induction variables then */
933     if ( indVars ) {
934         eBBlock *preHdr = loopReg->entry->preHeader ;
935         iCode *icFirst = NULL , *icLast = NULL ;
936         induction *ip;  
937         bitVect *indVect = NULL;
938         
939         /* create an iCode chain from it */
940         for (ip = setFirstItem(indVars); 
941              ip ; 
942              ip = setNextItem(indVars)) {
943
944             indVect = bitVectSetBit(indVect,ip->ic->key);
945             ip->ic->lineno = preHdr->ech->lineno;
946             if (!icFirst)
947                 icFirst = ip->ic;
948             if (icLast) {
949                 icLast->next = ip->ic;
950                 ip->ic->prev = icLast;
951                 icLast = ip->ic ;
952             } else 
953                 icLast = ip->ic;        
954             change++ ;      
955         }
956        
957         /* add the instruction chain to the end of the */
958         /* preheader for this loop                     */
959         preHdr->ech->next = icFirst ;
960         icFirst->prev = preHdr->ech ;
961         preHdr->ech = icLast;
962         icLast->next = NULL;            
963         
964         /* add the induction variable vector to the last
965            block in the loop */
966         lastBlock->isLastInLoop = 1;
967         lastBlock->linds = indVect;
968     }
969     
970     setToNull ((void **)&indVars);
971     return change ;    
972 }
973
974 /*-----------------------------------------------------------------*/
975 /* mergeRegions - will merge region with same entry point           */
976 /*-----------------------------------------------------------------*/
977 DEFSETFUNC(mergeRegions)
978 {
979     region *theLoop = item;
980     V_ARG(set*,allRegion) ;
981     region *lp ;
982     
983     /* if this has already been merged then do nothing */
984     if (theLoop->merged)
985         return 0;
986
987     /* go thru all the region and check if any of them have the */
988     /* entryPoint as the Loop                                  */
989     for (lp = setFirstItem(allRegion); lp ; lp = setNextItem(allRegion)) {
990
991         if (lp == theLoop)
992             continue ;
993
994         if (lp->entry == theLoop->entry) {
995             theLoop->regBlocks = unionSets (theLoop->regBlocks,
996                                              lp->regBlocks,THROW_BOTH);
997             lp->merged = 1;
998         }
999     }
1000
1001     return 1;
1002 }
1003
1004 /*-----------------------------------------------------------------*/
1005 /* ifMerged - return 1 if the merge flag is 1                      */
1006 /*-----------------------------------------------------------------*/
1007 DEFSETFUNC(ifMerged)
1008 {
1009     region *lp = item;
1010
1011     return lp->merged ;
1012 }
1013
1014 /*-----------------------------------------------------------------*/
1015 /* mergeInnerLoops - will merge into body when entry is present    */
1016 /*-----------------------------------------------------------------*/
1017 DEFSETFUNC(mergeInnerLoops)
1018 {
1019     region *theLoop = item;
1020     V_ARG(set *,allRegion);
1021     V_ARG(int *,maxDepth);
1022     region *lp;
1023     
1024     /* check if the entry point is present in the body of any */
1025     /* loop then put the body of this loop into the outer loop*/
1026     for (lp = setFirstItem(allRegion); lp ; lp = setNextItem(allRegion)) {
1027
1028         if ( lp == theLoop )
1029             continue ;
1030
1031         if (isinSet(lp->regBlocks, theLoop->entry)) {
1032             lp->containsLoops += theLoop->containsLoops + 1 ;
1033             if ( lp->containsLoops > (*maxDepth))
1034                 *maxDepth = lp->containsLoops;
1035
1036             lp->regBlocks = unionSets (lp->regBlocks,
1037                                         theLoop->regBlocks,THROW_DEST);
1038         }
1039     }
1040
1041     return 1;
1042 }
1043
1044
1045 /*-----------------------------------------------------------------*/
1046 /* createLoopRegions - will detect and create a set of natural loops */
1047 /*-----------------------------------------------------------------*/
1048 hTab *createLoopRegions (eBBlock **ebbs , int count  )
1049 {   
1050     set *allRegion  = NULL; /* set of all loops */       
1051     hTab *orderedLoops = NULL ;
1052     set *bEdges = NULL;
1053     int maxDepth = 0;
1054     region *lp;
1055
1056     /* get all the back edges in the graph */
1057     if (! applyToSet(graphEdges,backEdges,&bEdges))
1058         return 0 ; /* found no loops */
1059
1060     /* for each of these back edges get the blocks that */
1061     /* constitute the loops                             */
1062     applyToSet(bEdges,createLoop,&allRegion);
1063
1064     /* now we will create regions from these loops               */
1065     /* loops with the same entry points are considered to be the */
1066     /* same loop & they are merged. If the entry point of a loop */
1067     /* is found in the body of another loop then , all the blocks*/
1068     /* in that loop are added to the loops containing the header */    
1069     applyToSet(allRegion, mergeRegions , allRegion);
1070
1071     /* delete those already merged */
1072     deleteItemIf (&allRegion, ifMerged);
1073
1074     applyToSet(allRegion, mergeInnerLoops, allRegion, &maxDepth);
1075     maxDepth++;
1076     /* now create all the exits .. also */
1077     /* create an ordered set of loops   */
1078     /* i.e. we process loops in the inner to outer order */    
1079     for (lp = setFirstItem(allRegion) ; lp ; lp = setNextItem(allRegion)) {
1080         applyToSet (lp->regBlocks,addToExitsMarkDepth,
1081                     lp->regBlocks,&lp->exits,
1082                     (maxDepth - lp->containsLoops),lp);
1083         
1084         hTabAddItem (&orderedLoops,lp->containsLoops,lp);       
1085
1086     }
1087     return orderedLoops ;
1088 }
1089
1090 /*-----------------------------------------------------------------*/
1091 /* loopOptimizations - identify region & remove invariants & ind   */
1092 /*-----------------------------------------------------------------*/
1093 int loopOptimizations (hTab *orderedLoops, eBBlock **ebbs, int count)
1094 {
1095     region *lp ;
1096     int change = 0 ;
1097     int k;
1098
1099
1100     /* if no loop optimizations requested */
1101     if (! optimize.loopInvariant &&
1102         ! optimize.loopInduction )
1103         return 0;
1104
1105     /* now we process the loops inner to outer order */
1106     /* this is essential to maintain data flow information */
1107     /* the other choice is an ugly iteration for the depth */
1108     /* of the loops would hate that */
1109     for ( lp = hTabFirstItem(orderedLoops,&k); lp ; 
1110           lp = hTabNextItem(orderedLoops,&k)) {
1111         
1112         if (optimize.loopInvariant) 
1113             change += loopInvariants(lp, ebbs, count);       
1114         
1115         if (optimize.loopInduction)
1116             change += loopInduction(lp, ebbs, count);
1117     }
1118         
1119     return change;
1120 }