1169689Skan/* Tail call optimization on trees.
2169689Skan   Copyright (C) 2003, 2004, 2005 Free Software Foundation, Inc.
3169689Skan
4169689SkanThis file is part of GCC.
5169689Skan
6169689SkanGCC is free software; you can redistribute it and/or modify
7169689Skanit under the terms of the GNU General Public License as published by
8169689Skanthe Free Software Foundation; either version 2, or (at your option)
9169689Skanany later version.
10169689Skan
11169689SkanGCC is distributed in the hope that it will be useful,
12169689Skanbut WITHOUT ANY WARRANTY; without even the implied warranty of
13169689SkanMERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14169689SkanGNU General Public License for more details.
15169689Skan
16169689SkanYou should have received a copy of the GNU General Public License
17169689Skanalong with GCC; see the file COPYING.  If not, write to
18169689Skanthe Free Software Foundation, 51 Franklin Street, Fifth Floor,
19169689SkanBoston, MA 02110-1301, USA.  */
20169689Skan
21169689Skan#include "config.h"
22169689Skan#include "system.h"
23169689Skan#include "coretypes.h"
24169689Skan#include "tm.h"
25169689Skan#include "tree.h"
26169689Skan#include "rtl.h"
27169689Skan#include "tm_p.h"
28169689Skan#include "hard-reg-set.h"
29169689Skan#include "basic-block.h"
30169689Skan#include "function.h"
31169689Skan#include "tree-flow.h"
32169689Skan#include "tree-dump.h"
33169689Skan#include "diagnostic.h"
34169689Skan#include "except.h"
35169689Skan#include "tree-pass.h"
36169689Skan#include "flags.h"
37169689Skan#include "langhooks.h"
38169689Skan
39169689Skan/* The file implements the tail recursion elimination.  It is also used to
40169689Skan   analyze the tail calls in general, passing the results to the rtl level
41169689Skan   where they are used for sibcall optimization.
42169689Skan
43169689Skan   In addition to the standard tail recursion elimination, we handle the most
44169689Skan   trivial cases of making the call tail recursive by creating accumulators.
45169689Skan   For example the following function
46169689Skan
47169689Skan   int sum (int n)
48169689Skan   {
49169689Skan     if (n > 0)
50169689Skan       return n + sum (n - 1);
51169689Skan     else
52169689Skan       return 0;
53169689Skan   }
54169689Skan
55169689Skan   is transformed into
56169689Skan
57169689Skan   int sum (int n)
58169689Skan   {
59169689Skan     int acc = 0;
60169689Skan
61169689Skan     while (n > 0)
62169689Skan       acc += n--;
63169689Skan
64169689Skan     return acc;
65169689Skan   }
66169689Skan
67169689Skan   To do this, we maintain two accumulators (a_acc and m_acc) that indicate
68169689Skan   when we reach the return x statement, we should return a_acc + x * m_acc
69169689Skan   instead.  They are initially initialized to 0 and 1, respectively,
70169689Skan   so the semantics of the function is obviously preserved.  If we are
71169689Skan   guaranteed that the value of the accumulator never change, we
72169689Skan   omit the accumulator.
73169689Skan
74169689Skan   There are three cases how the function may exit.  The first one is
75169689Skan   handled in adjust_return_value, the other two in adjust_accumulator_values
76169689Skan   (the second case is actually a special case of the third one and we
77169689Skan   present it separately just for clarity):
78169689Skan
79169689Skan   1) Just return x, where x is not in any of the remaining special shapes.
80169689Skan      We rewrite this to a gimple equivalent of return m_acc * x + a_acc.
81169689Skan
82169689Skan   2) return f (...), where f is the current function, is rewritten in a
83169689Skan      classical tail-recursion elimination way, into assignment of arguments
84169689Skan      and jump to the start of the function.  Values of the accumulators
85169689Skan      are unchanged.
86169689Skan
87169689Skan   3) return a + m * f(...), where a and m do not depend on call to f.
88169689Skan      To preserve the semantics described before we want this to be rewritten
89169689Skan      in such a way that we finally return
90169689Skan
91169689Skan      a_acc + (a + m * f(...)) * m_acc = (a_acc + a * m_acc) + (m * m_acc) * f(...).
92169689Skan
93169689Skan      I.e. we increase a_acc by a * m_acc, multiply m_acc by m and
94169689Skan      eliminate the tail call to f.  Special cases when the value is just
95169689Skan      added or just multiplied are obtained by setting a = 0 or m = 1.
96169689Skan
97169689Skan   TODO -- it is possible to do similar tricks for other operations.  */
98169689Skan
99169689Skan/* A structure that describes the tailcall.  */
100169689Skan
101169689Skanstruct tailcall
102169689Skan{
103169689Skan  /* The block in that the call occur.  */
104169689Skan  basic_block call_block;
105169689Skan
106169689Skan  /* The iterator pointing to the call statement.  */
107169689Skan  block_stmt_iterator call_bsi;
108169689Skan
109169689Skan  /* True if it is a call to the current function.  */
110169689Skan  bool tail_recursion;
111169689Skan
112169689Skan  /* The return value of the caller is mult * f + add, where f is the return
113169689Skan     value of the call.  */
114169689Skan  tree mult, add;
115169689Skan
116169689Skan  /* Next tailcall in the chain.  */
117169689Skan  struct tailcall *next;
118169689Skan};
119169689Skan
120169689Skan/* The variables holding the value of multiplicative and additive
121169689Skan   accumulator.  */
122169689Skanstatic tree m_acc, a_acc;
123169689Skan
124169689Skanstatic bool suitable_for_tail_opt_p (void);
125169689Skanstatic bool optimize_tail_call (struct tailcall *, bool);
126169689Skanstatic void eliminate_tail_call (struct tailcall *);
127169689Skanstatic void find_tail_calls (basic_block, struct tailcall **);
128169689Skan
129169689Skan/* Returns false when the function is not suitable for tail call optimization
130169689Skan   from some reason (e.g. if it takes variable number of arguments).  */
131169689Skan
132169689Skanstatic bool
133169689Skansuitable_for_tail_opt_p (void)
134169689Skan{
135169689Skan  referenced_var_iterator rvi;
136169689Skan  tree var;
137169689Skan
138169689Skan  if (current_function_stdarg)
139169689Skan    return false;
140169689Skan
141169689Skan  /* No local variable nor structure field should be call-clobbered.  We
142169689Skan     ignore any kind of memory tag, as these are not real variables.  */
143169689Skan
144169689Skan  FOR_EACH_REFERENCED_VAR (var, rvi)
145169689Skan    {
146169689Skan
147169689Skan      if (!is_global_var (var)
148169689Skan	  && (!MTAG_P (var) || TREE_CODE (var) == STRUCT_FIELD_TAG)
149169689Skan	  && is_call_clobbered (var))
150169689Skan	return false;
151169689Skan    }
152169689Skan
153169689Skan  return true;
154169689Skan}
155169689Skan/* Returns false when the function is not suitable for tail call optimization
156169689Skan   from some reason (e.g. if it takes variable number of arguments).
157169689Skan   This test must pass in addition to suitable_for_tail_opt_p in order to make
158169689Skan   tail call discovery happen.  */
159169689Skan
160169689Skanstatic bool
161169689Skansuitable_for_tail_call_opt_p (void)
162169689Skan{
163169689Skan  tree param;
164169689Skan
165169689Skan  /* alloca (until we have stack slot life analysis) inhibits
166169689Skan     sibling call optimizations, but not tail recursion.  */
167169689Skan  if (current_function_calls_alloca)
168169689Skan    return false;
169169689Skan
170169689Skan  /* If we are using sjlj exceptions, we may need to add a call to
171169689Skan     _Unwind_SjLj_Unregister at exit of the function.  Which means
172169689Skan     that we cannot do any sibcall transformations.  */
173169689Skan  if (USING_SJLJ_EXCEPTIONS && current_function_has_exception_handlers ())
174169689Skan    return false;
175169689Skan
176169689Skan  /* Any function that calls setjmp might have longjmp called from
177169689Skan     any called function.  ??? We really should represent this
178169689Skan     properly in the CFG so that this needn't be special cased.  */
179169689Skan  if (current_function_calls_setjmp)
180169689Skan    return false;
181169689Skan
182169689Skan  /* ??? It is OK if the argument of a function is taken in some cases,
183169689Skan     but not in all cases.  See PR15387 and PR19616.  Revisit for 4.1.  */
184169689Skan  for (param = DECL_ARGUMENTS (current_function_decl);
185169689Skan       param;
186169689Skan       param = TREE_CHAIN (param))
187169689Skan    if (TREE_ADDRESSABLE (param))
188169689Skan      return false;
189169689Skan
190169689Skan  return true;
191169689Skan}
192169689Skan
193169689Skan/* Checks whether the expression EXPR in stmt AT is independent of the
194169689Skan   statement pointed to by BSI (in a sense that we already know EXPR's value
195169689Skan   at BSI).  We use the fact that we are only called from the chain of
196169689Skan   basic blocks that have only single successor.  Returns the expression
197169689Skan   containing the value of EXPR at BSI.  */
198169689Skan
199169689Skanstatic tree
200169689Skanindependent_of_stmt_p (tree expr, tree at, block_stmt_iterator bsi)
201169689Skan{
202169689Skan  basic_block bb, call_bb, at_bb;
203169689Skan  edge e;
204169689Skan  edge_iterator ei;
205169689Skan
206169689Skan  if (is_gimple_min_invariant (expr))
207169689Skan    return expr;
208169689Skan
209169689Skan  if (TREE_CODE (expr) != SSA_NAME)
210169689Skan    return NULL_TREE;
211169689Skan
212169689Skan  /* Mark the blocks in the chain leading to the end.  */
213169689Skan  at_bb = bb_for_stmt (at);
214169689Skan  call_bb = bb_for_stmt (bsi_stmt (bsi));
215169689Skan  for (bb = call_bb; bb != at_bb; bb = single_succ (bb))
216169689Skan    bb->aux = &bb->aux;
217169689Skan  bb->aux = &bb->aux;
218169689Skan
219169689Skan  while (1)
220169689Skan    {
221169689Skan      at = SSA_NAME_DEF_STMT (expr);
222169689Skan      bb = bb_for_stmt (at);
223169689Skan
224169689Skan      /* The default definition or defined before the chain.  */
225169689Skan      if (!bb || !bb->aux)
226169689Skan	break;
227169689Skan
228169689Skan      if (bb == call_bb)
229169689Skan	{
230169689Skan	  for (; !bsi_end_p (bsi); bsi_next (&bsi))
231169689Skan	    if (bsi_stmt (bsi) == at)
232169689Skan	      break;
233169689Skan
234169689Skan	  if (!bsi_end_p (bsi))
235169689Skan	    expr = NULL_TREE;
236169689Skan	  break;
237169689Skan	}
238169689Skan
239169689Skan      if (TREE_CODE (at) != PHI_NODE)
240169689Skan	{
241169689Skan	  expr = NULL_TREE;
242169689Skan	  break;
243169689Skan	}
244169689Skan
245169689Skan      FOR_EACH_EDGE (e, ei, bb->preds)
246169689Skan	if (e->src->aux)
247169689Skan	  break;
248169689Skan      gcc_assert (e);
249169689Skan
250169689Skan      expr = PHI_ARG_DEF_FROM_EDGE (at, e);
251169689Skan      if (TREE_CODE (expr) != SSA_NAME)
252169689Skan	{
253169689Skan	  /* The value is a constant.  */
254169689Skan	  break;
255169689Skan	}
256169689Skan    }
257169689Skan
258169689Skan  /* Unmark the blocks.  */
259169689Skan  for (bb = call_bb; bb != at_bb; bb = single_succ (bb))
260169689Skan    bb->aux = NULL;
261169689Skan  bb->aux = NULL;
262169689Skan
263169689Skan  return expr;
264169689Skan}
265169689Skan
266169689Skan/* Simulates the effect of an assignment of ASS in STMT on the return value
267169689Skan   of the tail recursive CALL passed in ASS_VAR.  M and A are the
268169689Skan   multiplicative and the additive factor for the real return value.  */
269169689Skan
270169689Skanstatic bool
271169689Skanprocess_assignment (tree ass, tree stmt, block_stmt_iterator call, tree *m,
272169689Skan		    tree *a, tree *ass_var)
273169689Skan{
274169689Skan  tree op0, op1, non_ass_var;
275169689Skan  tree dest = TREE_OPERAND (ass, 0);
276169689Skan  tree src = TREE_OPERAND (ass, 1);
277169689Skan  enum tree_code code = TREE_CODE (src);
278169689Skan  tree src_var = src;
279169689Skan
280169689Skan  /* See if this is a simple copy operation of an SSA name to the function
281169689Skan     result.  In that case we may have a simple tail call.  Ignore type
282169689Skan     conversions that can never produce extra code between the function
283169689Skan     call and the function return.  */
284169689Skan  STRIP_NOPS (src_var);
285169689Skan  if (TREE_CODE (src_var) == SSA_NAME)
286169689Skan    {
287169689Skan      if (src_var != *ass_var)
288169689Skan	return false;
289169689Skan
290169689Skan      *ass_var = dest;
291169689Skan      return true;
292169689Skan    }
293169689Skan
294169689Skan  if (TREE_CODE_CLASS (code) != tcc_binary)
295169689Skan    return false;
296169689Skan
297169689Skan  /* Accumulator optimizations will reverse the order of operations.
298169689Skan     We can only do that for floating-point types if we're assuming
299169689Skan     that addition and multiplication are associative.  */
300169689Skan  if (!flag_unsafe_math_optimizations)
301169689Skan    if (FLOAT_TYPE_P (TREE_TYPE (DECL_RESULT (current_function_decl))))
302169689Skan      return false;
303169689Skan
304169689Skan  /* We only handle the code like
305169689Skan
306169689Skan     x = call ();
307169689Skan     y = m * x;
308169689Skan     z = y + a;
309169689Skan     return z;
310169689Skan
311169689Skan     TODO -- Extend it for cases where the linear transformation of the output
312169689Skan     is expressed in a more complicated way.  */
313169689Skan
314169689Skan  op0 = TREE_OPERAND (src, 0);
315169689Skan  op1 = TREE_OPERAND (src, 1);
316169689Skan
317169689Skan  if (op0 == *ass_var
318169689Skan      && (non_ass_var = independent_of_stmt_p (op1, stmt, call)))
319169689Skan    ;
320169689Skan  else if (op1 == *ass_var
321169689Skan	   && (non_ass_var = independent_of_stmt_p (op0, stmt, call)))
322169689Skan    ;
323169689Skan  else
324169689Skan    return false;
325169689Skan
326169689Skan  switch (code)
327169689Skan    {
328169689Skan    case PLUS_EXPR:
329169689Skan      /* There should be no previous addition.  TODO -- it should be fairly
330169689Skan	 straightforward to lift this restriction -- just allow storing
331169689Skan	 more complicated expressions in *A, and gimplify it in
332169689Skan	 adjust_accumulator_values.  */
333169689Skan      if (*a)
334169689Skan	return false;
335169689Skan      *a = non_ass_var;
336169689Skan      *ass_var = dest;
337169689Skan      return true;
338169689Skan
339169689Skan    case MULT_EXPR:
340169689Skan      /* Similar remark applies here.  Handling multiplication after addition
341169689Skan	 is just slightly more complicated -- we need to multiply both *A and
342169689Skan	 *M.  */
343169689Skan      if (*a || *m)
344169689Skan	return false;
345169689Skan      *m = non_ass_var;
346169689Skan      *ass_var = dest;
347169689Skan      return true;
348169689Skan
349169689Skan      /* TODO -- Handle other codes (NEGATE_EXPR, MINUS_EXPR).  */
350169689Skan
351169689Skan    default:
352169689Skan      return false;
353169689Skan    }
354169689Skan}
355169689Skan
356169689Skan/* Propagate VAR through phis on edge E.  */
357169689Skan
358169689Skanstatic tree
359169689Skanpropagate_through_phis (tree var, edge e)
360169689Skan{
361169689Skan  basic_block dest = e->dest;
362169689Skan  tree phi;
363169689Skan
364169689Skan  for (phi = phi_nodes (dest); phi; phi = PHI_CHAIN (phi))
365169689Skan    if (PHI_ARG_DEF_FROM_EDGE (phi, e) == var)
366169689Skan      return PHI_RESULT (phi);
367169689Skan
368169689Skan  return var;
369169689Skan}
370169689Skan
371169689Skan/* Finds tailcalls falling into basic block BB. The list of found tailcalls is
372169689Skan   added to the start of RET.  */
373169689Skan
374169689Skanstatic void
375169689Skanfind_tail_calls (basic_block bb, struct tailcall **ret)
376169689Skan{
377169689Skan  tree ass_var, ret_var, stmt, func, param, args, call = NULL_TREE;
378169689Skan  block_stmt_iterator bsi, absi;
379169689Skan  bool tail_recursion;
380169689Skan  struct tailcall *nw;
381169689Skan  edge e;
382169689Skan  tree m, a;
383169689Skan  basic_block abb;
384169689Skan  stmt_ann_t ann;
385169689Skan
386169689Skan  if (!single_succ_p (bb))
387169689Skan    return;
388169689Skan
389169689Skan  for (bsi = bsi_last (bb); !bsi_end_p (bsi); bsi_prev (&bsi))
390169689Skan    {
391169689Skan      stmt = bsi_stmt (bsi);
392169689Skan
393169689Skan      /* Ignore labels.  */
394169689Skan      if (TREE_CODE (stmt) == LABEL_EXPR)
395169689Skan	continue;
396169689Skan
397169689Skan      /* Check for a call.  */
398169689Skan      if (TREE_CODE (stmt) == MODIFY_EXPR)
399169689Skan	{
400169689Skan	  ass_var = TREE_OPERAND (stmt, 0);
401169689Skan	  call = TREE_OPERAND (stmt, 1);
402169689Skan	  if (TREE_CODE (call) == WITH_SIZE_EXPR)
403169689Skan	    call = TREE_OPERAND (call, 0);
404169689Skan	}
405169689Skan      else
406169689Skan	{
407169689Skan	  ass_var = NULL_TREE;
408169689Skan	  call = stmt;
409169689Skan	}
410169689Skan
411169689Skan      if (TREE_CODE (call) == CALL_EXPR)
412169689Skan	break;
413169689Skan
414169689Skan      /* If the statement has virtual or volatile operands, fail.  */
415169689Skan      ann = stmt_ann (stmt);
416169689Skan      if (!ZERO_SSA_OPERANDS (stmt, (SSA_OP_VUSE | SSA_OP_VIRTUAL_DEFS))
417169689Skan	  || ann->has_volatile_ops)
418169689Skan	return;
419169689Skan    }
420169689Skan
421169689Skan  if (bsi_end_p (bsi))
422169689Skan    {
423169689Skan      edge_iterator ei;
424169689Skan      /* Recurse to the predecessors.  */
425169689Skan      FOR_EACH_EDGE (e, ei, bb->preds)
426169689Skan	find_tail_calls (e->src, ret);
427169689Skan
428169689Skan      return;
429169689Skan    }
430169689Skan
431169689Skan  /* We found the call, check whether it is suitable.  */
432169689Skan  tail_recursion = false;
433169689Skan  func = get_callee_fndecl (call);
434169689Skan  if (func == current_function_decl)
435169689Skan    {
436169689Skan      for (param = DECL_ARGUMENTS (func), args = TREE_OPERAND (call, 1);
437169689Skan	   param && args;
438169689Skan	   param = TREE_CHAIN (param), args = TREE_CHAIN (args))
439169689Skan	{
440169689Skan	  tree arg = TREE_VALUE (args);
441169689Skan	  if (param != arg)
442169689Skan	    {
443169689Skan	      /* Make sure there are no problems with copying.  The parameter
444169689Skan	         have a copyable type and the two arguments must have reasonably
445169689Skan	         equivalent types.  The latter requirement could be relaxed if
446169689Skan	         we emitted a suitable type conversion statement.  */
447169689Skan	      if (!is_gimple_reg_type (TREE_TYPE (param))
448169689Skan		  || !lang_hooks.types_compatible_p (TREE_TYPE (param),
449169689Skan						     TREE_TYPE (arg)))
450169689Skan		break;
451169689Skan
452169689Skan	      /* The parameter should be a real operand, so that phi node
453169689Skan		 created for it at the start of the function has the meaning
454169689Skan		 of copying the value.  This test implies is_gimple_reg_type
455169689Skan		 from the previous condition, however this one could be
456169689Skan		 relaxed by being more careful with copying the new value
457169689Skan		 of the parameter (emitting appropriate MODIFY_EXPR and
458169689Skan		 updating the virtual operands).  */
459169689Skan	      if (!is_gimple_reg (param))
460169689Skan		break;
461169689Skan	    }
462169689Skan	}
463169689Skan      if (!args && !param)
464169689Skan	tail_recursion = true;
465169689Skan    }
466169689Skan
467169689Skan  /* Now check the statements after the call.  None of them has virtual
468169689Skan     operands, so they may only depend on the call through its return
469169689Skan     value.  The return value should also be dependent on each of them,
470169689Skan     since we are running after dce.  */
471169689Skan  m = NULL_TREE;
472169689Skan  a = NULL_TREE;
473169689Skan
474169689Skan  abb = bb;
475169689Skan  absi = bsi;
476169689Skan  while (1)
477169689Skan    {
478169689Skan      bsi_next (&absi);
479169689Skan
480169689Skan      while (bsi_end_p (absi))
481169689Skan	{
482169689Skan	  ass_var = propagate_through_phis (ass_var, single_succ_edge (abb));
483169689Skan	  abb = single_succ (abb);
484169689Skan	  absi = bsi_start (abb);
485169689Skan	}
486169689Skan
487169689Skan      stmt = bsi_stmt (absi);
488169689Skan
489169689Skan      if (TREE_CODE (stmt) == LABEL_EXPR)
490169689Skan	continue;
491169689Skan
492169689Skan      if (TREE_CODE (stmt) == RETURN_EXPR)
493169689Skan	break;
494169689Skan
495169689Skan      if (TREE_CODE (stmt) != MODIFY_EXPR)
496169689Skan	return;
497169689Skan
498169689Skan      if (!process_assignment (stmt, stmt, bsi, &m, &a, &ass_var))
499169689Skan	return;
500169689Skan    }
501169689Skan
502169689Skan  /* See if this is a tail call we can handle.  */
503169689Skan  ret_var = TREE_OPERAND (stmt, 0);
504169689Skan  if (ret_var
505169689Skan      && TREE_CODE (ret_var) == MODIFY_EXPR)
506169689Skan    {
507169689Skan      tree ret_op = TREE_OPERAND (ret_var, 1);
508169689Skan      STRIP_NOPS (ret_op);
509169689Skan      if (!tail_recursion
510169689Skan	  && TREE_CODE (ret_op) != SSA_NAME)
511169689Skan	return;
512169689Skan
513169689Skan      if (!process_assignment (ret_var, stmt, bsi, &m, &a, &ass_var))
514169689Skan	return;
515169689Skan      ret_var = TREE_OPERAND (ret_var, 0);
516169689Skan    }
517169689Skan
518169689Skan  /* We may proceed if there either is no return value, or the return value
519169689Skan     is identical to the call's return.  */
520169689Skan  if (ret_var
521169689Skan      && (ret_var != ass_var))
522169689Skan    return;
523169689Skan
524169689Skan  /* If this is not a tail recursive call, we cannot handle addends or
525169689Skan     multiplicands.  */
526169689Skan  if (!tail_recursion && (m || a))
527169689Skan    return;
528169689Skan
529169689Skan  nw = XNEW (struct tailcall);
530169689Skan
531169689Skan  nw->call_block = bb;
532169689Skan  nw->call_bsi = bsi;
533169689Skan
534169689Skan  nw->tail_recursion = tail_recursion;
535169689Skan
536169689Skan  nw->mult = m;
537169689Skan  nw->add = a;
538169689Skan
539169689Skan  nw->next = *ret;
540169689Skan  *ret = nw;
541169689Skan}
542169689Skan
543169689Skan/* Adjust the accumulator values according to A and M after BSI, and update
544169689Skan   the phi nodes on edge BACK.  */
545169689Skan
546169689Skanstatic void
547169689Skanadjust_accumulator_values (block_stmt_iterator bsi, tree m, tree a, edge back)
548169689Skan{
549169689Skan  tree stmt, var, phi, tmp;
550169689Skan  tree ret_type = TREE_TYPE (DECL_RESULT (current_function_decl));
551169689Skan  tree a_acc_arg = a_acc, m_acc_arg = m_acc;
552169689Skan
553169689Skan  if (a)
554169689Skan    {
555169689Skan      if (m_acc)
556169689Skan	{
557169689Skan	  if (integer_onep (a))
558169689Skan	    var = m_acc;
559169689Skan	  else
560169689Skan	    {
561169689Skan	      stmt = build2 (MODIFY_EXPR, ret_type, NULL_TREE,
562169689Skan			     build2 (MULT_EXPR, ret_type, m_acc, a));
563169689Skan
564169689Skan	      tmp = create_tmp_var (ret_type, "acc_tmp");
565169689Skan	      add_referenced_var (tmp);
566169689Skan
567169689Skan	      var = make_ssa_name (tmp, stmt);
568169689Skan	      TREE_OPERAND (stmt, 0) = var;
569169689Skan	      bsi_insert_after (&bsi, stmt, BSI_NEW_STMT);
570169689Skan	    }
571169689Skan	}
572169689Skan      else
573169689Skan	var = a;
574169689Skan
575169689Skan      stmt = build2 (MODIFY_EXPR, ret_type, NULL_TREE,
576169689Skan		     build2 (PLUS_EXPR, ret_type, a_acc, var));
577169689Skan      var = make_ssa_name (SSA_NAME_VAR (a_acc), stmt);
578169689Skan      TREE_OPERAND (stmt, 0) = var;
579169689Skan      bsi_insert_after (&bsi, stmt, BSI_NEW_STMT);
580169689Skan      a_acc_arg = var;
581169689Skan    }
582169689Skan
583169689Skan  if (m)
584169689Skan    {
585169689Skan      stmt = build2 (MODIFY_EXPR, ret_type, NULL_TREE,
586169689Skan		     build2 (MULT_EXPR, ret_type, m_acc, m));
587169689Skan      var = make_ssa_name (SSA_NAME_VAR (m_acc), stmt);
588169689Skan      TREE_OPERAND (stmt, 0) = var;
589169689Skan      bsi_insert_after (&bsi, stmt, BSI_NEW_STMT);
590169689Skan      m_acc_arg = var;
591169689Skan    }
592169689Skan
593169689Skan  if (a_acc)
594169689Skan    {
595169689Skan      for (phi = phi_nodes (back->dest); phi; phi = PHI_CHAIN (phi))
596169689Skan	if (PHI_RESULT (phi) == a_acc)
597169689Skan	  break;
598169689Skan
599169689Skan      add_phi_arg (phi, a_acc_arg, back);
600169689Skan    }
601169689Skan
602169689Skan  if (m_acc)
603169689Skan    {
604169689Skan      for (phi = phi_nodes (back->dest); phi; phi = PHI_CHAIN (phi))
605169689Skan	if (PHI_RESULT (phi) == m_acc)
606169689Skan	  break;
607169689Skan
608169689Skan      add_phi_arg (phi, m_acc_arg, back);
609169689Skan    }
610169689Skan}
611169689Skan
612169689Skan/* Adjust value of the return at the end of BB according to M and A
613169689Skan   accumulators.  */
614169689Skan
615169689Skanstatic void
616169689Skanadjust_return_value (basic_block bb, tree m, tree a)
617169689Skan{
618169689Skan  tree ret_stmt = last_stmt (bb), ret_var, var, stmt, tmp;
619169689Skan  tree ret_type = TREE_TYPE (DECL_RESULT (current_function_decl));
620169689Skan  block_stmt_iterator bsi = bsi_last (bb);
621169689Skan
622169689Skan  gcc_assert (TREE_CODE (ret_stmt) == RETURN_EXPR);
623169689Skan
624169689Skan  ret_var = TREE_OPERAND (ret_stmt, 0);
625169689Skan  if (!ret_var)
626169689Skan    return;
627169689Skan
628169689Skan  if (TREE_CODE (ret_var) == MODIFY_EXPR)
629169689Skan    {
630169689Skan      ret_var->common.ann = (tree_ann_t) stmt_ann (ret_stmt);
631169689Skan      bsi_replace (&bsi, ret_var, true);
632169689Skan      SSA_NAME_DEF_STMT (TREE_OPERAND (ret_var, 0)) = ret_var;
633169689Skan      ret_var = TREE_OPERAND (ret_var, 0);
634169689Skan      ret_stmt = build1 (RETURN_EXPR, TREE_TYPE (ret_stmt), ret_var);
635169689Skan      bsi_insert_after (&bsi, ret_stmt, BSI_NEW_STMT);
636169689Skan    }
637169689Skan
638169689Skan  if (m)
639169689Skan    {
640169689Skan      stmt = build2 (MODIFY_EXPR, ret_type, NULL_TREE,
641169689Skan		     build2 (MULT_EXPR, ret_type, m_acc, ret_var));
642169689Skan
643169689Skan      tmp = create_tmp_var (ret_type, "acc_tmp");
644169689Skan      add_referenced_var (tmp);
645169689Skan
646169689Skan      var = make_ssa_name (tmp, stmt);
647169689Skan      TREE_OPERAND (stmt, 0) = var;
648169689Skan      bsi_insert_before (&bsi, stmt, BSI_SAME_STMT);
649169689Skan    }
650169689Skan  else
651169689Skan    var = ret_var;
652169689Skan
653169689Skan  if (a)
654169689Skan    {
655169689Skan      stmt = build2 (MODIFY_EXPR, ret_type, NULL_TREE,
656169689Skan		     build2 (PLUS_EXPR, ret_type, a_acc, var));
657169689Skan
658169689Skan      tmp = create_tmp_var (ret_type, "acc_tmp");
659169689Skan      add_referenced_var (tmp);
660169689Skan
661169689Skan      var = make_ssa_name (tmp, stmt);
662169689Skan      TREE_OPERAND (stmt, 0) = var;
663169689Skan      bsi_insert_before (&bsi, stmt, BSI_SAME_STMT);
664169689Skan    }
665169689Skan
666169689Skan  TREE_OPERAND (ret_stmt, 0) = var;
667169689Skan  update_stmt (ret_stmt);
668169689Skan}
669169689Skan
670169689Skan/* Subtract COUNT and FREQUENCY from the basic block and it's
671169689Skan   outgoing edge.  */
672169689Skanstatic void
673169689Skandecrease_profile (basic_block bb, gcov_type count, int frequency)
674169689Skan{
675169689Skan  edge e;
676169689Skan  bb->count -= count;
677169689Skan  if (bb->count < 0)
678169689Skan    bb->count = 0;
679169689Skan  bb->frequency -= frequency;
680169689Skan  if (bb->frequency < 0)
681169689Skan    bb->frequency = 0;
682169689Skan  if (!single_succ_p (bb))
683169689Skan    {
684169689Skan      gcc_assert (!EDGE_COUNT (bb->succs));
685169689Skan      return;
686169689Skan    }
687169689Skan  e = single_succ_edge (bb);
688169689Skan  e->count -= count;
689169689Skan  if (e->count < 0)
690169689Skan    e->count = 0;
691169689Skan}
692169689Skan
693169689Skan/* Returns true if argument PARAM of the tail recursive call needs to be copied
694169689Skan   when the call is eliminated.  */
695169689Skan
696169689Skanstatic bool
697169689Skanarg_needs_copy_p (tree param)
698169689Skan{
699169689Skan  tree def;
700169689Skan
701169689Skan  if (!is_gimple_reg (param) || !var_ann (param))
702169689Skan    return false;
703169689Skan
704169689Skan  /* Parameters that are only defined but never used need not be copied.  */
705169689Skan  def = default_def (param);
706169689Skan  if (!def)
707169689Skan    return false;
708169689Skan
709169689Skan  return true;
710169689Skan}
711169689Skan
712169689Skan/* Eliminates tail call described by T.  TMP_VARS is a list of
713169689Skan   temporary variables used to copy the function arguments.  */
714169689Skan
715169689Skanstatic void
716169689Skaneliminate_tail_call (struct tailcall *t)
717169689Skan{
718169689Skan  tree param, stmt, args, rslt, call;
719169689Skan  basic_block bb, first;
720169689Skan  edge e;
721169689Skan  tree phi;
722169689Skan  block_stmt_iterator bsi;
723169689Skan  tree orig_stmt;
724169689Skan
725169689Skan  stmt = orig_stmt = bsi_stmt (t->call_bsi);
726169689Skan  bb = t->call_block;
727169689Skan
728169689Skan  if (dump_file && (dump_flags & TDF_DETAILS))
729169689Skan    {
730169689Skan      fprintf (dump_file, "Eliminated tail recursion in bb %d : ",
731169689Skan	       bb->index);
732169689Skan      print_generic_stmt (dump_file, stmt, TDF_SLIM);
733169689Skan      fprintf (dump_file, "\n");
734169689Skan    }
735169689Skan
736169689Skan  if (TREE_CODE (stmt) == MODIFY_EXPR)
737169689Skan    stmt = TREE_OPERAND (stmt, 1);
738169689Skan
739169689Skan  first = single_succ (ENTRY_BLOCK_PTR);
740169689Skan
741169689Skan  /* Remove the code after call_bsi that will become unreachable.  The
742169689Skan     possibly unreachable code in other blocks is removed later in
743169689Skan     cfg cleanup.  */
744169689Skan  bsi = t->call_bsi;
745169689Skan  bsi_next (&bsi);
746169689Skan  while (!bsi_end_p (bsi))
747169689Skan    {
748169689Skan      tree t = bsi_stmt (bsi);
749169689Skan      /* Do not remove the return statement, so that redirect_edge_and_branch
750169689Skan	 sees how the block ends.  */
751169689Skan      if (TREE_CODE (t) == RETURN_EXPR)
752169689Skan	break;
753169689Skan
754169689Skan      bsi_remove (&bsi, true);
755169689Skan      release_defs (t);
756169689Skan    }
757169689Skan
758169689Skan  /* Number of executions of function has reduced by the tailcall.  */
759169689Skan  e = single_succ_edge (t->call_block);
760169689Skan  decrease_profile (EXIT_BLOCK_PTR, e->count, EDGE_FREQUENCY (e));
761169689Skan  decrease_profile (ENTRY_BLOCK_PTR, e->count, EDGE_FREQUENCY (e));
762169689Skan  if (e->dest != EXIT_BLOCK_PTR)
763169689Skan    decrease_profile (e->dest, e->count, EDGE_FREQUENCY (e));
764169689Skan
765169689Skan  /* Replace the call by a jump to the start of function.  */
766169689Skan  e = redirect_edge_and_branch (single_succ_edge (t->call_block), first);
767169689Skan  gcc_assert (e);
768169689Skan  PENDING_STMT (e) = NULL_TREE;
769169689Skan
770169689Skan  /* Add phi node entries for arguments.  The ordering of the phi nodes should
771169689Skan     be the same as the ordering of the arguments.  */
772169689Skan  for (param = DECL_ARGUMENTS (current_function_decl),
773169689Skan       args = TREE_OPERAND (stmt, 1),
774169689Skan       phi = phi_nodes (first);
775169689Skan       param;
776169689Skan       param = TREE_CHAIN (param),
777169689Skan       args = TREE_CHAIN (args))
778169689Skan    {
779169689Skan      if (!arg_needs_copy_p (param))
780169689Skan	continue;
781169689Skan      gcc_assert (param == SSA_NAME_VAR (PHI_RESULT (phi)));
782169689Skan
783169689Skan      add_phi_arg (phi, TREE_VALUE (args), e);
784169689Skan      phi = PHI_CHAIN (phi);
785169689Skan    }
786169689Skan
787169689Skan  /* Update the values of accumulators.  */
788169689Skan  adjust_accumulator_values (t->call_bsi, t->mult, t->add, e);
789169689Skan
790169689Skan  call = bsi_stmt (t->call_bsi);
791169689Skan  if (TREE_CODE (call) == MODIFY_EXPR)
792169689Skan    {
793169689Skan      rslt = TREE_OPERAND (call, 0);
794169689Skan
795169689Skan      /* Result of the call will no longer be defined.  So adjust the
796169689Skan	 SSA_NAME_DEF_STMT accordingly.  */
797169689Skan      SSA_NAME_DEF_STMT (rslt) = build_empty_stmt ();
798169689Skan    }
799169689Skan
800169689Skan  bsi_remove (&t->call_bsi, true);
801169689Skan  release_defs (call);
802169689Skan}
803169689Skan
804169689Skan/* Add phi nodes for the virtual operands defined in the function to the
805169689Skan   header of the loop created by tail recursion elimination.
806169689Skan
807169689Skan   Originally, we used to add phi nodes only for call clobbered variables,
808169689Skan   as the value of the non-call clobbered ones obviously cannot be used
809169689Skan   or changed within the recursive call.  However, the local variables
810169689Skan   from multiple calls now share the same location, so the virtual ssa form
811169689Skan   requires us to say that the location dies on further iterations of the loop,
812169689Skan   which requires adding phi nodes.
813169689Skan*/
814169689Skanstatic void
815169689Skanadd_virtual_phis (void)
816169689Skan{
817169689Skan  referenced_var_iterator rvi;
818169689Skan  tree var;
819169689Skan
820169689Skan  /* The problematic part is that there is no way how to know what
821169689Skan     to put into phi nodes (there in fact does not have to be such
822169689Skan     ssa name available).  A solution would be to have an artificial
823169689Skan     use/kill for all virtual operands in EXIT node.  Unless we have
824169689Skan     this, we cannot do much better than to rebuild the ssa form for
825169689Skan     possibly affected virtual ssa names from scratch.  */
826169689Skan
827169689Skan  FOR_EACH_REFERENCED_VAR (var, rvi)
828169689Skan    {
829169689Skan      if (!is_gimple_reg (var) && default_def (var) != NULL_TREE)
830169689Skan	mark_sym_for_renaming (var);
831169689Skan    }
832169689Skan
833169689Skan  update_ssa (TODO_update_ssa_only_virtuals);
834169689Skan}
835169689Skan
836169689Skan/* Optimizes the tailcall described by T.  If OPT_TAILCALLS is true, also
837169689Skan   mark the tailcalls for the sibcall optimization.  */
838169689Skan
839169689Skanstatic bool
840169689Skanoptimize_tail_call (struct tailcall *t, bool opt_tailcalls)
841169689Skan{
842169689Skan  if (t->tail_recursion)
843169689Skan    {
844169689Skan      eliminate_tail_call (t);
845169689Skan      return true;
846169689Skan    }
847169689Skan
848169689Skan  if (opt_tailcalls)
849169689Skan    {
850169689Skan      tree stmt = bsi_stmt (t->call_bsi);
851169689Skan
852169689Skan      stmt = get_call_expr_in (stmt);
853169689Skan      CALL_EXPR_TAILCALL (stmt) = 1;
854169689Skan      if (dump_file && (dump_flags & TDF_DETAILS))
855169689Skan        {
856169689Skan	  fprintf (dump_file, "Found tail call ");
857169689Skan	  print_generic_expr (dump_file, stmt, dump_flags);
858169689Skan	  fprintf (dump_file, " in bb %i\n", t->call_block->index);
859169689Skan	}
860169689Skan    }
861169689Skan
862169689Skan  return false;
863169689Skan}
864169689Skan
865169689Skan/* Optimizes tail calls in the function, turning the tail recursion
866169689Skan   into iteration.  */
867169689Skan
868169689Skanstatic void
869169689Skantree_optimize_tail_calls_1 (bool opt_tailcalls)
870169689Skan{
871169689Skan  edge e;
872169689Skan  bool phis_constructed = false;
873169689Skan  struct tailcall *tailcalls = NULL, *act, *next;
874169689Skan  bool changed = false;
875169689Skan  basic_block first = single_succ (ENTRY_BLOCK_PTR);
876169689Skan  tree stmt, param, ret_type, tmp, phi;
877169689Skan  edge_iterator ei;
878169689Skan
879169689Skan  if (!suitable_for_tail_opt_p ())
880169689Skan    return;
881169689Skan  if (opt_tailcalls)
882169689Skan    opt_tailcalls = suitable_for_tail_call_opt_p ();
883169689Skan
884169689Skan  FOR_EACH_EDGE (e, ei, EXIT_BLOCK_PTR->preds)
885169689Skan    {
886169689Skan      /* Only traverse the normal exits, i.e. those that end with return
887169689Skan	 statement.  */
888169689Skan      stmt = last_stmt (e->src);
889169689Skan
890169689Skan      if (stmt
891169689Skan	  && TREE_CODE (stmt) == RETURN_EXPR)
892169689Skan	find_tail_calls (e->src, &tailcalls);
893169689Skan    }
894169689Skan
895169689Skan  /* Construct the phi nodes and accumulators if necessary.  */
896169689Skan  a_acc = m_acc = NULL_TREE;
897169689Skan  for (act = tailcalls; act; act = act->next)
898169689Skan    {
899169689Skan      if (!act->tail_recursion)
900169689Skan	continue;
901169689Skan
902169689Skan      if (!phis_constructed)
903169689Skan	{
904169689Skan	  /* Ensure that there is only one predecessor of the block.  */
905169689Skan	  if (!single_pred_p (first))
906169689Skan	    first = split_edge (single_succ_edge (ENTRY_BLOCK_PTR));
907169689Skan
908169689Skan	  /* Copy the args if needed.  */
909169689Skan	  for (param = DECL_ARGUMENTS (current_function_decl);
910169689Skan	       param;
911169689Skan	       param = TREE_CHAIN (param))
912169689Skan	    if (arg_needs_copy_p (param))
913169689Skan	      {
914169689Skan		tree name = default_def (param);
915169689Skan		tree new_name = make_ssa_name (param, SSA_NAME_DEF_STMT (name));
916169689Skan		tree phi;
917169689Skan
918169689Skan		set_default_def (param, new_name);
919169689Skan		phi = create_phi_node (name, first);
920169689Skan		SSA_NAME_DEF_STMT (name) = phi;
921169689Skan		add_phi_arg (phi, new_name, single_pred_edge (first));
922169689Skan	      }
923169689Skan	  phis_constructed = true;
924169689Skan	}
925169689Skan
926169689Skan      if (act->add && !a_acc)
927169689Skan	{
928169689Skan	  ret_type = TREE_TYPE (DECL_RESULT (current_function_decl));
929169689Skan
930169689Skan	  tmp = create_tmp_var (ret_type, "add_acc");
931169689Skan	  add_referenced_var (tmp);
932169689Skan
933169689Skan	  phi = create_phi_node (tmp, first);
934169689Skan	  add_phi_arg (phi,
935169689Skan		       /* RET_TYPE can be a float when -ffast-maths is
936169689Skan			  enabled.  */
937169689Skan		       fold_convert (ret_type, integer_zero_node),
938169689Skan		       single_pred_edge (first));
939169689Skan	  a_acc = PHI_RESULT (phi);
940169689Skan	}
941169689Skan
942169689Skan      if (act->mult && !m_acc)
943169689Skan	{
944169689Skan	  ret_type = TREE_TYPE (DECL_RESULT (current_function_decl));
945169689Skan
946169689Skan	  tmp = create_tmp_var (ret_type, "mult_acc");
947169689Skan	  add_referenced_var (tmp);
948169689Skan
949169689Skan	  phi = create_phi_node (tmp, first);
950169689Skan	  add_phi_arg (phi,
951169689Skan		       /* RET_TYPE can be a float when -ffast-maths is
952169689Skan			  enabled.  */
953169689Skan		       fold_convert (ret_type, integer_one_node),
954169689Skan		       single_pred_edge (first));
955169689Skan	  m_acc = PHI_RESULT (phi);
956169689Skan	}
957169689Skan    }
958169689Skan
959169689Skan
960169689Skan  if (phis_constructed)
961169689Skan    {
962169689Skan      /* Reverse the order of the phi nodes, so that it matches the order
963169689Skan	 of operands of the function, as assumed by eliminate_tail_call.  */
964169689Skan      set_phi_nodes (first, phi_reverse (phi_nodes (first)));
965169689Skan    }
966169689Skan
967169689Skan  for (; tailcalls; tailcalls = next)
968169689Skan    {
969169689Skan      next = tailcalls->next;
970169689Skan      changed |= optimize_tail_call (tailcalls, opt_tailcalls);
971169689Skan      free (tailcalls);
972169689Skan    }
973169689Skan
974169689Skan  if (a_acc || m_acc)
975169689Skan    {
976169689Skan      /* Modify the remaining return statements.  */
977169689Skan      FOR_EACH_EDGE (e, ei, EXIT_BLOCK_PTR->preds)
978169689Skan	{
979169689Skan	  stmt = last_stmt (e->src);
980169689Skan
981169689Skan	  if (stmt
982169689Skan	      && TREE_CODE (stmt) == RETURN_EXPR)
983169689Skan	    adjust_return_value (e->src, m_acc, a_acc);
984169689Skan	}
985169689Skan    }
986169689Skan
987169689Skan  if (changed)
988169689Skan    {
989169689Skan      free_dominance_info (CDI_DOMINATORS);
990169689Skan      cleanup_tree_cfg ();
991169689Skan    }
992169689Skan
993169689Skan  if (phis_constructed)
994169689Skan    add_virtual_phis ();
995169689Skan}
996169689Skan
997169689Skanstatic unsigned int
998169689Skanexecute_tail_recursion (void)
999169689Skan{
1000169689Skan  tree_optimize_tail_calls_1 (false);
1001169689Skan  return 0;
1002169689Skan}
1003169689Skan
1004169689Skanstatic bool
1005169689Skangate_tail_calls (void)
1006169689Skan{
1007169689Skan  return flag_optimize_sibling_calls != 0;
1008169689Skan}
1009169689Skan
1010169689Skanstatic unsigned int
1011169689Skanexecute_tail_calls (void)
1012169689Skan{
1013169689Skan  tree_optimize_tail_calls_1 (true);
1014169689Skan  return 0;
1015169689Skan}
1016169689Skan
1017169689Skanstruct tree_opt_pass pass_tail_recursion =
1018169689Skan{
1019169689Skan  "tailr",				/* name */
1020169689Skan  gate_tail_calls,			/* gate */
1021169689Skan  execute_tail_recursion,		/* execute */
1022169689Skan  NULL,					/* sub */
1023169689Skan  NULL,					/* next */
1024169689Skan  0,					/* static_pass_number */
1025169689Skan  0,					/* tv_id */
1026169689Skan  PROP_cfg | PROP_ssa | PROP_alias,	/* properties_required */
1027169689Skan  0,					/* properties_provided */
1028169689Skan  0,					/* properties_destroyed */
1029169689Skan  0,					/* todo_flags_start */
1030169689Skan  TODO_dump_func | TODO_verify_ssa,	/* todo_flags_finish */
1031169689Skan  0					/* letter */
1032169689Skan};
1033169689Skan
1034169689Skanstruct tree_opt_pass pass_tail_calls =
1035169689Skan{
1036169689Skan  "tailc",				/* name */
1037169689Skan  gate_tail_calls,			/* gate */
1038169689Skan  execute_tail_calls,			/* execute */
1039169689Skan  NULL,					/* sub */
1040169689Skan  NULL,					/* next */
1041169689Skan  0,					/* static_pass_number */
1042169689Skan  0,					/* tv_id */
1043169689Skan  PROP_cfg | PROP_ssa | PROP_alias,	/* properties_required */
1044169689Skan  0,					/* properties_provided */
1045169689Skan  0,					/* properties_destroyed */
1046169689Skan  0,					/* todo_flags_start */
1047169689Skan  TODO_dump_func | TODO_verify_ssa,	/* todo_flags_finish */
1048169689Skan  0					/* letter */
1049169689Skan};
1050