fix pr68692: reinstantiate the copy of internal parameters
[platform/upstream/gcc.git] / gcc / graphite-isl-ast-to-gimple.c
1 /* Translation of isl AST to Gimple.
2    Copyright (C) 2014-2016 Free Software Foundation, Inc.
3    Contributed by Roman Gareev <gareevroman@gmail.com>.
4
5 This file is part of GCC.
6
7 GCC is free software; you can redistribute it and/or modify
8 it under the terms of the GNU General Public License as published by
9 the Free Software Foundation; either version 3, or (at your option)
10 any later version.
11
12 GCC 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 GCC; see the file COPYING3.  If not see
19 <http://www.gnu.org/licenses/>.  */
20
21 #define USES_ISL
22
23 #include "config.h"
24
25 #ifdef HAVE_isl
26
27 #include "system.h"
28 #include "coretypes.h"
29 #include "backend.h"
30 #include "cfghooks.h"
31 #include "tree.h"
32 #include "gimple.h"
33 #include "params.h"
34 #include "fold-const.h"
35 #include "gimple-fold.h"
36 #include "gimple-iterator.h"
37 #include "gimplify.h"
38 #include "gimplify-me.h"
39 #include "tree-eh.h"
40 #include "tree-ssa-loop.h"
41 #include "tree-ssa-operands.h"
42 #include "tree-ssa-propagate.h"
43 #include "tree-pass.h"
44 #include "cfgloop.h"
45 #include "tree-data-ref.h"
46 #include "tree-ssa-loop-manip.h"
47 #include "tree-scalar-evolution.h"
48 #include "gimple-ssa.h"
49 #include "tree-phinodes.h"
50 #include "tree-into-ssa.h"
51 #include "ssa-iterators.h"
52 #include "tree-cfg.h"
53 #include "gimple-pretty-print.h"
54 #include "cfganal.h"
55 #include "value-prof.h"
56 #include "graphite.h"
57 #include <map>
58
59 /* We always try to use signed 128 bit types, but fall back to smaller types
60    in case a platform does not provide types of these sizes. In the future we
61    should use isl to derive the optimal type for each subexpression.  */
62
63 static int max_mode_int_precision =
64   GET_MODE_PRECISION (mode_for_size (MAX_FIXED_MODE_SIZE, MODE_INT, 0));
65 static int graphite_expression_type_precision = 128 <= max_mode_int_precision ?
66                                                 128 : max_mode_int_precision;
67
68 struct ast_build_info
69 {
70   ast_build_info()
71     : is_parallelizable(false)
72   { }
73   bool is_parallelizable;
74 };
75
76 /* Converts a GMP constant VAL to a tree and returns it.  */
77
78 static tree
79 gmp_cst_to_tree (tree type, mpz_t val)
80 {
81   tree t = type ? type : integer_type_node;
82   mpz_t tmp;
83
84   mpz_init (tmp);
85   mpz_set (tmp, val);
86   wide_int wi = wi::from_mpz (t, tmp, true);
87   mpz_clear (tmp);
88
89   return wide_int_to_tree (t, wi);
90 }
91
92 /* Verifies properties that GRAPHITE should maintain during translation.  */
93
94 static inline void
95 graphite_verify (void)
96 {
97   checking_verify_loop_structure ();
98   checking_verify_loop_closed_ssa (true);
99 }
100
101 /* IVS_PARAMS maps isl's scattering and parameter identifiers
102    to corresponding trees.  */
103
104 typedef std::map<isl_id *, tree> ivs_params;
105
106 /* Free all memory allocated for isl's identifiers.  */
107
108 void ivs_params_clear (ivs_params &ip)
109 {
110   std::map<isl_id *, tree>::iterator it;
111   for (it = ip.begin ();
112        it != ip.end (); it++)
113     {
114       isl_id_free (it->first);
115     }
116 }
117
118 #ifdef HAVE_ISL_OPTIONS_SET_SCHEDULE_SERIALIZE_SCCS
119
120 /* Set the "separate" option for the schedule node.  */
121
122 static __isl_give isl_schedule_node *
123 set_separate_option (__isl_take isl_schedule_node *node, void *user)
124 {
125   if (user)
126     return node;
127
128   if (isl_schedule_node_get_type (node) != isl_schedule_node_band)
129     return node;
130
131   /* Set the "separate" option unless it is set earlier to another option.  */
132   if (isl_schedule_node_band_member_get_ast_loop_type (node, 0)
133       == isl_ast_loop_default)
134     return isl_schedule_node_band_member_set_ast_loop_type
135       (node, 0, isl_ast_loop_separate);
136
137   return node;
138 }
139 #endif
140
141 class translate_isl_ast_to_gimple
142 {
143  public:
144   translate_isl_ast_to_gimple (sese_info_p r)
145     : region (r), codegen_error (false)
146     { }
147
148   /* Translates an isl AST node NODE to GCC representation in the
149      context of a SESE.  */
150   edge translate_isl_ast (loop_p context_loop, __isl_keep isl_ast_node *node,
151                           edge next_e, ivs_params &ip);
152
153   /* Translates an isl_ast_node_for to Gimple.  */
154   edge translate_isl_ast_node_for (loop_p context_loop,
155                                    __isl_keep isl_ast_node *node,
156                                    edge next_e, ivs_params &ip);
157
158   /* Create the loop for a isl_ast_node_for.
159
160      - NEXT_E is the edge where new generated code should be attached.  */
161   edge translate_isl_ast_for_loop (loop_p context_loop,
162                                    __isl_keep isl_ast_node *node_for,
163                                    edge next_e,
164                                    tree type, tree lb, tree ub,
165                                    ivs_params &ip);
166
167   /* Translates an isl_ast_node_if to Gimple.  */
168   edge translate_isl_ast_node_if (loop_p context_loop,
169                                   __isl_keep isl_ast_node *node,
170                                   edge next_e, ivs_params &ip);
171
172   /* Translates an isl_ast_node_user to Gimple.
173
174      FIXME: We should remove iv_map.create (loop->num + 1), if it is
175      possible.  */
176   edge translate_isl_ast_node_user (__isl_keep isl_ast_node *node,
177                                     edge next_e, ivs_params &ip);
178
179   /* Translates an isl_ast_node_block to Gimple.  */
180   edge translate_isl_ast_node_block (loop_p context_loop,
181                                      __isl_keep isl_ast_node *node,
182                                      edge next_e, ivs_params &ip);
183
184   /* Converts a unary isl_ast_expr_op expression E to a GCC expression tree of
185      type TYPE.  */
186   tree unary_op_to_tree (tree type, __isl_take isl_ast_expr *expr,
187                          ivs_params &ip);
188
189   /* Converts a binary isl_ast_expr_op expression E to a GCC expression tree of
190      type TYPE.  */
191   tree binary_op_to_tree (tree type, __isl_take isl_ast_expr *expr,
192                           ivs_params &ip);
193
194   /* Converts a ternary isl_ast_expr_op expression E to a GCC expression tree of
195      type TYPE.  */
196   tree ternary_op_to_tree (tree type, __isl_take isl_ast_expr *expr,
197                            ivs_params &ip);
198
199   /* Converts an isl_ast_expr_op expression E with unknown number of arguments
200      to a GCC expression tree of type TYPE.  */
201   tree nary_op_to_tree (tree type, __isl_take isl_ast_expr *expr,
202                         ivs_params &ip);
203
204   /* Converts an isl AST expression E back to a GCC expression tree of
205      type TYPE.  */
206   tree gcc_expression_from_isl_expression (tree type,
207                                            __isl_take isl_ast_expr *,
208                                            ivs_params &ip);
209
210   /* Return the tree variable that corresponds to the given isl ast identifier
211      expression (an isl_ast_expr of type isl_ast_expr_id).
212
213      FIXME: We should replace blind conversation of id's type with derivation
214      of the optimal type when we get the corresponding isl support.  Blindly
215      converting type sizes may be problematic when we switch to smaller
216      types.  */
217   tree gcc_expression_from_isl_ast_expr_id (tree type,
218                                             __isl_keep isl_ast_expr *expr_id,
219                                             ivs_params &ip);
220
221   /* Converts an isl_ast_expr_int expression E to a GCC expression tree of
222      type TYPE.  */
223   tree gcc_expression_from_isl_expr_int (tree type,
224                                          __isl_take isl_ast_expr *expr);
225
226   /* Converts an isl_ast_expr_op expression E to a GCC expression tree of
227      type TYPE.  */
228   tree gcc_expression_from_isl_expr_op (tree type,
229                                         __isl_take isl_ast_expr *expr,
230                                         ivs_params &ip);
231
232   /* Creates a new LOOP corresponding to isl_ast_node_for.  Inserts an
233      induction variable for the new LOOP.  New LOOP is attached to CFG
234      starting at ENTRY_EDGE.  LOOP is inserted into the loop tree and
235      becomes the child loop of the OUTER_LOOP.  NEWIVS_INDEX binds
236      isl's scattering name to the induction variable created for the
237      loop of STMT.  The new induction variable is inserted in the NEWIVS
238      vector and is of type TYPE.  */
239   struct loop *graphite_create_new_loop (edge entry_edge,
240                                          __isl_keep isl_ast_node *node_for,
241                                          loop_p outer, tree type,
242                                          tree lb, tree ub, ivs_params &ip);
243
244   /* All loops generated by create_empty_loop_on_edge have the form of
245      a post-test loop:
246
247      do
248
249      {
250      body of the loop;
251      } while (lower bound < upper bound);
252
253      We create a new if region protecting the loop to be executed, if
254      the execution count is zero (lower bound > upper bound).  */
255   edge graphite_create_new_loop_guard (edge entry_edge,
256                                        __isl_keep isl_ast_node *node_for,
257                                        tree *type,
258                                        tree *lb, tree *ub, ivs_params &ip);
259
260   /* Creates a new if region corresponding to isl's cond.  */
261   edge graphite_create_new_guard (edge entry_edge,
262                                   __isl_take isl_ast_expr *if_cond,
263                                   ivs_params &ip);
264
265   /* Inserts in iv_map a tuple (OLD_LOOP->num, NEW_NAME) for the induction
266      variables of the loops around GBB in SESE.
267
268      FIXME: Instead of using a vec<tree> that maps each loop id to a possible
269      chrec, we could consider using a map<int, tree> that maps loop ids to the
270      corresponding tree expressions.  */
271   void build_iv_mapping (vec<tree> iv_map, gimple_poly_bb_p gbb,
272                          __isl_keep isl_ast_expr *user_expr, ivs_params &ip,
273                          sese_l &region);
274
275   /* Patch the missing arguments of the phi nodes.  */
276
277   void translate_pending_phi_nodes (void);
278
279   /* Add isl's parameter identifiers and corresponding trees to ivs_params.  */
280
281   void add_parameters_to_ivs_params (scop_p scop, ivs_params &ip);
282
283   /* Get the maximal number of schedule dimensions in the scop SCOP.  */
284
285   int get_max_schedule_dimensions (scop_p scop);
286
287   /* Generates a build, which specifies the constraints on the parameters.  */
288
289   __isl_give isl_ast_build *generate_isl_context (scop_p scop);
290
291   /* Extend the schedule to NB_SCHEDULE_DIMS schedule dimensions.
292
293      For schedules with different dimensionality, the isl AST generator can not
294      define an order and will just randomly choose an order.  The solution to
295      this problem is to extend all schedules to the maximal number of schedule
296      dimensions (using '0's for the remaining values).  */
297
298   __isl_give isl_map *extend_schedule (__isl_take isl_map *schedule,
299                                        int nb_schedule_dims);
300
301   /* Generates a schedule, which specifies an order used to
302      visit elements in a domain.  */
303
304   __isl_give isl_union_map *generate_isl_schedule (scop_p scop);
305
306 #ifdef HAVE_ISL_OPTIONS_SET_SCHEDULE_SERIALIZE_SCCS
307   /* Set the "separate" option for all schedules.  This helps reducing control
308      overhead.  */
309
310   __isl_give isl_schedule *
311     set_options_for_schedule_tree (__isl_take isl_schedule *schedule);
312 #endif
313
314   /* Set the separate option for all dimensions.
315      This helps to reduce control overhead.  */
316
317   __isl_give isl_ast_build * set_options (__isl_take isl_ast_build *control,
318                                           __isl_keep isl_union_map *schedule);
319
320   /* Generate isl AST from schedule of SCOP.  Also, collects IVS_PARAMS in
321      IP.  */
322
323   __isl_give isl_ast_node * scop_to_isl_ast (scop_p scop, ivs_params &ip);
324
325
326   /* Return true if RENAME (defined in BB) is a valid use in NEW_BB.  The
327      definition should flow into use, and the use should respect the loop-closed
328      SSA form.  */
329
330   bool is_valid_rename (tree rename, basic_block def_bb, basic_block use_bb,
331                         bool loop_phi, tree old_name, basic_block old_bb) const;
332
333   /* Returns the expression associated to OLD_NAME (which is used in OLD_BB), in
334      NEW_BB from RENAME_MAP.  LOOP_PHI is true when we want to rename OLD_NAME
335      within a loop PHI instruction.  */
336
337   tree get_rename (basic_block new_bb, tree old_name,
338                    basic_block old_bb, bool loop_phi) const;
339
340   /* For ops which are scev_analyzeable, we can regenerate a new name from
341   its scalar evolution around LOOP.  */
342
343   tree get_rename_from_scev (tree old_name, gimple_seq *stmts, loop_p loop,
344                              basic_block new_bb, basic_block old_bb,
345                              vec<tree> iv_map);
346
347   /* Returns a basic block that could correspond to where a constant was defined
348      in the original code.  In the original code OLD_BB had the definition, we
349      need to find which basic block out of the copies of old_bb, in the new
350      region, should a definition correspond to if it has to reach BB.  */
351
352   basic_block get_def_bb_for_const (basic_block bb, basic_block old_bb) const;
353
354   /* Get the new name of OP (from OLD_BB) to be used in NEW_BB.  LOOP_PHI is
355      true when we want to rename an OP within a loop PHI instruction.  */
356
357   tree get_new_name (basic_block new_bb, tree op,
358                      basic_block old_bb, bool loop_phi) const;
359
360   /* Collect all the operands of NEW_EXPR by recursively visiting each
361      operand.  */
362
363   void collect_all_ssa_names (tree new_expr, vec<tree> *vec_ssa);
364
365   /* Copy the PHI arguments from OLD_PHI to the NEW_PHI.  The arguments to
366      NEW_PHI must be found unless they can be POSTPONEd for later.  */
367
368   bool copy_loop_phi_args (gphi *old_phi, init_back_edge_pair_t &ibp_old_bb,
369                            gphi *new_phi, init_back_edge_pair_t &ibp_new_bb,
370                            bool postpone);
371
372   /* Copy loop phi nodes from BB to NEW_BB.  */
373
374   bool copy_loop_phi_nodes (basic_block bb, basic_block new_bb);
375
376   /* Add phi nodes to all merge points of all the diamonds enclosing the loop of
377      the close phi node PHI.  */
378
379   bool add_close_phis_to_merge_points (gphi *old_phi, gphi *new_phi,
380                                        tree default_value);
381
382   tree add_close_phis_to_outer_loops (tree last_merge_name, edge merge_e,
383                                       gimple *old_close_phi);
384
385   /* Copy all the loop-close phi args from BB to NEW_BB.  */
386
387   bool copy_loop_close_phi_args (basic_block old_bb, basic_block new_bb,
388                                  bool postpone);
389
390   /* Copy loop close phi nodes from BB to NEW_BB.  */
391
392   bool copy_loop_close_phi_nodes (basic_block old_bb, basic_block new_bb);
393
394   /* Copy the arguments of cond-phi node PHI, to NEW_PHI in the codegenerated
395      region.  If postpone is true and it isn't possible to copy any arg of PHI,
396      the PHI is added to the REGION->INCOMPLETE_PHIS to be codegenerated later.
397      Returns false if the copying was unsuccessful.  */
398
399   bool copy_cond_phi_args (gphi *phi, gphi *new_phi, vec<tree> iv_map,
400                            bool postpone);
401
402   /* Copy cond phi nodes from BB to NEW_BB.  A cond-phi node is a basic block
403   containing phi nodes coming from two predecessors, and none of them are back
404   edges.  */
405
406   bool copy_cond_phi_nodes (basic_block bb, basic_block new_bb,
407                             vec<tree> iv_map);
408
409   /* Duplicates the statements of basic block BB into basic block NEW_BB
410      and compute the new induction variables according to the IV_MAP.
411      CODEGEN_ERROR is set when the code generation cannot continue.  */
412
413   bool graphite_copy_stmts_from_block (basic_block bb, basic_block new_bb,
414                                        vec<tree> iv_map);
415
416   /* Copies BB and includes in the copied BB all the statements that can
417      be reached following the use-def chains from the memory accesses,
418      and returns the next edge following this new block.  codegen_error is
419      set when the code generation cannot continue.  */
420
421   edge copy_bb_and_scalar_dependences (basic_block bb, edge next_e,
422                                        vec<tree> iv_map);
423
424   /* Given a basic block containing close-phi it returns the new basic block
425      where to insert a copy of the close-phi nodes.  All the uses in close phis
426      should come from a single loop otherwise it returns NULL.  */
427   edge edge_for_new_close_phis (basic_block bb);
428
429   /* Add NEW_NAME as the ARGNUM-th arg of NEW_PHI which is in NEW_BB.
430      DOMINATING_PRED is the predecessor basic block of OLD_BB which dominates
431      the other pred of OLD_BB as well.  If no such basic block exists then it is
432      NULL.  NON_DOMINATING_PRED is a pred which does not dominate OLD_BB, it
433      cannot be NULL.
434
435      Case1: OLD_BB->preds {BB1, BB2} and BB1 does not dominate BB2 and vice
436      versa.  In this case DOMINATING_PRED = NULL.
437
438      Case2: OLD_BB->preds {BB1, BB2} and BB1 dominates BB2.
439
440      Returns true on successful copy of the args, false otherwise.  */
441
442   bool add_phi_arg_for_new_expr (tree old_phi_args[2], tree new_phi_args[2],
443                                  edge old_bb_dominating_edge,
444                                  edge old_bb_non_dominating_edge,
445                                  gphi *phi, gphi *new_phi,
446                                  basic_block new_bb);
447
448   /* Renames the scalar uses of the statement COPY, using the substitution map
449      RENAME_MAP, inserting the gimplification code at GSI_TGT, for the
450      translation REGION, with the original copied statement in LOOP, and using
451      the induction variable renaming map IV_MAP.  Returns true when something
452      has been renamed.  codegen_error is set when the code generation cannot
453      continue.  */
454
455   bool rename_uses (gimple *copy, gimple_stmt_iterator *gsi_tgt,
456                     basic_block old_bb, loop_p loop, vec<tree> iv_map);
457
458   /* Register in RENAME_MAP the rename tuple (OLD_NAME, EXPR).
459      When OLD_NAME and EXPR are the same we assert.  */
460
461   void set_rename (tree old_name, tree expr);
462
463   /* Create new names for all the definitions created by COPY and add
464      replacement mappings for each new name.  */
465
466   void set_rename_for_each_def (gimple *stmt);
467
468   /* Insert each statement from SEQ at its earliest insertion p.  */
469
470   void gsi_insert_earliest (gimple_seq seq);
471
472   /* Rename all the operands of NEW_EXPR by recursively visiting each
473      operand.  */
474
475   tree rename_all_uses (tree new_expr, basic_block new_bb, basic_block old_bb);
476
477   bool codegen_error_p () const
478   { return codegen_error; }
479
480   /* Prints NODE to FILE.  */
481
482   void print_isl_ast_node (FILE *file, __isl_keep isl_ast_node *node,
483                            __isl_keep isl_ctx *ctx) const;
484
485   /* Return true when OP is a constant tree.  */
486
487   bool is_constant (tree op) const
488   {
489     return TREE_CODE (op) == INTEGER_CST
490       || TREE_CODE (op) == REAL_CST
491       || TREE_CODE (op) == COMPLEX_CST
492       || TREE_CODE (op) == VECTOR_CST;
493   }
494
495 private:
496   /* The region to be translated.  */
497   sese_info_p region;
498
499   /* This flag is set when an error occurred during the translation of isl AST
500      to Gimple.  */
501   bool codegen_error;
502
503   /* A vector of all the edges at if_condition merge points.  */
504   auto_vec<edge, 2> merge_points;
505 };
506
507 /* Return the tree variable that corresponds to the given isl ast identifier
508    expression (an isl_ast_expr of type isl_ast_expr_id).
509
510    FIXME: We should replace blind conversion of id's type with derivation
511    of the optimal type when we get the corresponding isl support.  Blindly
512    converting type sizes may be problematic when we switch to smaller
513    types.  */
514
515 tree
516 translate_isl_ast_to_gimple::
517 gcc_expression_from_isl_ast_expr_id (tree type,
518                                      __isl_take isl_ast_expr *expr_id,
519                                      ivs_params &ip)
520 {
521   gcc_assert (isl_ast_expr_get_type (expr_id) == isl_ast_expr_id);
522   isl_id *tmp_isl_id = isl_ast_expr_get_id (expr_id);
523   std::map<isl_id *, tree>::iterator res;
524   res = ip.find (tmp_isl_id);
525   isl_id_free (tmp_isl_id);
526   gcc_assert (res != ip.end () &&
527               "Could not map isl_id to tree expression");
528   isl_ast_expr_free (expr_id);
529   tree t = res->second;
530   tree *val = region->parameter_rename_map->get(t);
531
532   if (!val)
533    val = &t;
534   return fold_convert (type, *val);
535 }
536
537 /* Converts an isl_ast_expr_int expression E to a GCC expression tree of
538    type TYPE.  */
539
540 tree
541 translate_isl_ast_to_gimple::
542 gcc_expression_from_isl_expr_int (tree type, __isl_take isl_ast_expr *expr)
543 {
544   gcc_assert (isl_ast_expr_get_type (expr) == isl_ast_expr_int);
545   isl_val *val = isl_ast_expr_get_val (expr);
546   mpz_t val_mpz_t;
547   mpz_init (val_mpz_t);
548   tree res;
549   if (isl_val_get_num_gmp (val, val_mpz_t) == -1)
550     res = NULL_TREE;
551   else
552     res = gmp_cst_to_tree (type, val_mpz_t);
553   isl_val_free (val);
554   isl_ast_expr_free (expr);
555   mpz_clear (val_mpz_t);
556   return res;
557 }
558
559 /* Converts a binary isl_ast_expr_op expression E to a GCC expression tree of
560    type TYPE.  */
561
562 tree
563 translate_isl_ast_to_gimple::
564 binary_op_to_tree (tree type, __isl_take isl_ast_expr *expr, ivs_params &ip)
565 {
566   isl_ast_expr *arg_expr = isl_ast_expr_get_op_arg (expr, 0);
567   tree tree_lhs_expr = gcc_expression_from_isl_expression (type, arg_expr, ip);
568   arg_expr = isl_ast_expr_get_op_arg (expr, 1);
569   tree tree_rhs_expr = gcc_expression_from_isl_expression (type, arg_expr, ip);
570
571   enum isl_ast_op_type expr_type = isl_ast_expr_get_op_type (expr);
572   isl_ast_expr_free (expr);
573
574   if (codegen_error)
575     return NULL_TREE;
576
577   switch (expr_type)
578     {
579     case isl_ast_op_add:
580       return fold_build2 (PLUS_EXPR, type, tree_lhs_expr, tree_rhs_expr);
581
582     case isl_ast_op_sub:
583       return fold_build2 (MINUS_EXPR, type, tree_lhs_expr, tree_rhs_expr);
584
585     case isl_ast_op_mul:
586       return fold_build2 (MULT_EXPR, type, tree_lhs_expr, tree_rhs_expr);
587
588     case isl_ast_op_div:
589       /* As isl operates on arbitrary precision numbers, we may end up with
590          division by 2^64 that is folded to 0.  */
591       if (integer_zerop (tree_rhs_expr))
592         {
593           codegen_error = true;
594           return NULL_TREE;
595         }
596       return fold_build2 (EXACT_DIV_EXPR, type, tree_lhs_expr, tree_rhs_expr);
597
598     case isl_ast_op_pdiv_q:
599       /* As isl operates on arbitrary precision numbers, we may end up with
600          division by 2^64 that is folded to 0.  */
601       if (integer_zerop (tree_rhs_expr))
602         {
603           codegen_error = true;
604           return NULL_TREE;
605         }
606       return fold_build2 (TRUNC_DIV_EXPR, type, tree_lhs_expr, tree_rhs_expr);
607
608 #if HAVE_ISL_OPTIONS_SET_SCHEDULE_SERIALIZE_SCCS
609     /* isl 0.15 or later.  */
610     case isl_ast_op_zdiv_r:
611 #endif
612     case isl_ast_op_pdiv_r:
613       /* As isl operates on arbitrary precision numbers, we may end up with
614          division by 2^64 that is folded to 0.  */
615       if (integer_zerop (tree_rhs_expr))
616         {
617           codegen_error = true;
618           return NULL_TREE;
619         }
620       return fold_build2 (TRUNC_MOD_EXPR, type, tree_lhs_expr, tree_rhs_expr);
621
622     case isl_ast_op_fdiv_q:
623       /* As isl operates on arbitrary precision numbers, we may end up with
624          division by 2^64 that is folded to 0.  */
625       if (integer_zerop (tree_rhs_expr))
626         {
627           codegen_error = true;
628           return NULL_TREE;
629         }
630       return fold_build2 (FLOOR_DIV_EXPR, type, tree_lhs_expr, tree_rhs_expr);
631
632     case isl_ast_op_and:
633       return fold_build2 (TRUTH_ANDIF_EXPR, type,
634                           tree_lhs_expr, tree_rhs_expr);
635
636     case isl_ast_op_or:
637       return fold_build2 (TRUTH_ORIF_EXPR, type, tree_lhs_expr, tree_rhs_expr);
638
639     case isl_ast_op_eq:
640       return fold_build2 (EQ_EXPR, type, tree_lhs_expr, tree_rhs_expr);
641
642     case isl_ast_op_le:
643       return fold_build2 (LE_EXPR, type, tree_lhs_expr, tree_rhs_expr);
644
645     case isl_ast_op_lt:
646       return fold_build2 (LT_EXPR, type, tree_lhs_expr, tree_rhs_expr);
647
648     case isl_ast_op_ge:
649       return fold_build2 (GE_EXPR, type, tree_lhs_expr, tree_rhs_expr);
650
651     case isl_ast_op_gt:
652       return fold_build2 (GT_EXPR, type, tree_lhs_expr, tree_rhs_expr);
653
654     default:
655       gcc_unreachable ();
656     }
657 }
658
659 /* Converts a ternary isl_ast_expr_op expression E to a GCC expression tree of
660    type TYPE.  */
661
662 tree
663 translate_isl_ast_to_gimple::
664 ternary_op_to_tree (tree type, __isl_take isl_ast_expr *expr, ivs_params &ip)
665 {
666   gcc_assert (isl_ast_expr_get_op_type (expr) == isl_ast_op_minus);
667   isl_ast_expr *arg_expr = isl_ast_expr_get_op_arg (expr, 0);
668   tree tree_first_expr
669     = gcc_expression_from_isl_expression (type, arg_expr, ip);
670   arg_expr = isl_ast_expr_get_op_arg (expr, 1);
671   tree tree_second_expr
672     = gcc_expression_from_isl_expression (type, arg_expr, ip);
673   arg_expr = isl_ast_expr_get_op_arg (expr, 2);
674   tree tree_third_expr
675     = gcc_expression_from_isl_expression (type, arg_expr, ip);
676   isl_ast_expr_free (expr);
677
678   if (codegen_error)
679     return NULL_TREE;
680   return fold_build3 (COND_EXPR, type, tree_first_expr,
681                       tree_second_expr, tree_third_expr);
682 }
683
684 /* Converts a unary isl_ast_expr_op expression E to a GCC expression tree of
685    type TYPE.  */
686
687 tree
688 translate_isl_ast_to_gimple::
689 unary_op_to_tree (tree type, __isl_take isl_ast_expr *expr, ivs_params &ip)
690 {
691   gcc_assert (isl_ast_expr_get_op_type (expr) == isl_ast_op_minus);
692   isl_ast_expr *arg_expr = isl_ast_expr_get_op_arg (expr, 0);
693   tree tree_expr = gcc_expression_from_isl_expression (type, arg_expr, ip);
694   isl_ast_expr_free (expr);
695   return codegen_error ? NULL_TREE : fold_build1 (NEGATE_EXPR, type, tree_expr);
696 }
697
698 /* Converts an isl_ast_expr_op expression E with unknown number of arguments
699    to a GCC expression tree of type TYPE.  */
700
701 tree
702 translate_isl_ast_to_gimple::
703 nary_op_to_tree (tree type, __isl_take isl_ast_expr *expr, ivs_params &ip)
704 {
705   enum tree_code op_code;
706   switch (isl_ast_expr_get_op_type (expr))
707     {
708     case isl_ast_op_max:
709       op_code = MAX_EXPR;
710       break;
711
712     case isl_ast_op_min:
713       op_code = MIN_EXPR;
714       break;
715
716     default:
717       gcc_unreachable ();    
718     }
719   isl_ast_expr *arg_expr = isl_ast_expr_get_op_arg (expr, 0);
720   tree res = gcc_expression_from_isl_expression (type, arg_expr, ip);
721
722   if (codegen_error)
723     {
724       isl_ast_expr_free (expr);
725       return NULL_TREE;
726     }
727
728   int i;
729   for (i = 1; i < isl_ast_expr_get_op_n_arg (expr); i++)
730     {
731       arg_expr = isl_ast_expr_get_op_arg (expr, i);
732       tree t = gcc_expression_from_isl_expression (type, arg_expr, ip);
733
734       if (codegen_error)
735         {
736           isl_ast_expr_free (expr);
737           return NULL_TREE;
738         }
739
740       res = fold_build2 (op_code, type, res, t);
741     }
742   isl_ast_expr_free (expr);
743   return res;
744 }
745
746 /* Converts an isl_ast_expr_op expression E to a GCC expression tree of
747    type TYPE.  */
748
749 tree
750 translate_isl_ast_to_gimple::
751 gcc_expression_from_isl_expr_op (tree type, __isl_take isl_ast_expr *expr,
752                                  ivs_params &ip)
753 {
754   if (codegen_error)
755     {
756       isl_ast_expr_free (expr);
757       return NULL_TREE;
758     }
759
760   gcc_assert (isl_ast_expr_get_type (expr) == isl_ast_expr_op);
761   switch (isl_ast_expr_get_op_type (expr))
762     {
763     /* These isl ast expressions are not supported yet.  */
764     case isl_ast_op_error:
765     case isl_ast_op_call:
766     case isl_ast_op_and_then:
767     case isl_ast_op_or_else:
768     case isl_ast_op_select:
769       gcc_unreachable ();
770
771     case isl_ast_op_max:
772     case isl_ast_op_min:
773       return nary_op_to_tree (type, expr, ip);
774
775     case isl_ast_op_add:
776     case isl_ast_op_sub:
777     case isl_ast_op_mul:
778     case isl_ast_op_div:
779     case isl_ast_op_pdiv_q:
780     case isl_ast_op_pdiv_r:
781     case isl_ast_op_fdiv_q:
782 #if HAVE_ISL_OPTIONS_SET_SCHEDULE_SERIALIZE_SCCS
783     /* isl 0.15 or later.  */
784     case isl_ast_op_zdiv_r:
785 #endif
786     case isl_ast_op_and:
787     case isl_ast_op_or:
788     case isl_ast_op_eq:
789     case isl_ast_op_le:
790     case isl_ast_op_lt:
791     case isl_ast_op_ge:
792     case isl_ast_op_gt:
793       return binary_op_to_tree (type, expr, ip);
794
795     case isl_ast_op_minus:
796       return unary_op_to_tree (type, expr, ip);
797
798     case isl_ast_op_cond:
799       return ternary_op_to_tree (type, expr, ip);
800
801     default:
802       gcc_unreachable ();
803     }
804
805   return NULL_TREE;
806 }
807
808 /* Converts an isl AST expression E back to a GCC expression tree of
809    type TYPE.  */
810
811 tree
812 translate_isl_ast_to_gimple::
813 gcc_expression_from_isl_expression (tree type, __isl_take isl_ast_expr *expr,
814                                     ivs_params &ip)
815 {
816   if (codegen_error)
817     {
818       isl_ast_expr_free (expr);
819       return NULL_TREE;
820     }
821
822   switch (isl_ast_expr_get_type (expr))
823     {
824     case isl_ast_expr_id:
825       return gcc_expression_from_isl_ast_expr_id (type, expr, ip);
826
827     case isl_ast_expr_int:
828       return gcc_expression_from_isl_expr_int (type, expr);
829
830     case isl_ast_expr_op:
831       return gcc_expression_from_isl_expr_op (type, expr, ip);
832
833     default:
834       gcc_unreachable ();
835     }
836
837   return NULL_TREE;
838 }
839
840 /* Creates a new LOOP corresponding to isl_ast_node_for.  Inserts an
841    induction variable for the new LOOP.  New LOOP is attached to CFG
842    starting at ENTRY_EDGE.  LOOP is inserted into the loop tree and
843    becomes the child loop of the OUTER_LOOP.  NEWIVS_INDEX binds
844    isl's scattering name to the induction variable created for the
845    loop of STMT.  The new induction variable is inserted in the NEWIVS
846    vector and is of type TYPE.  */
847
848 struct loop *
849 translate_isl_ast_to_gimple::
850 graphite_create_new_loop (edge entry_edge, __isl_keep isl_ast_node *node_for,
851                           loop_p outer, tree type, tree lb, tree ub,
852                           ivs_params &ip)
853 {
854   isl_ast_expr *for_inc = isl_ast_node_for_get_inc (node_for);
855   tree stride = gcc_expression_from_isl_expression (type, for_inc, ip);
856
857   /* To fail code generation, we generate wrong code until we discard it.  */
858   if (codegen_error)
859     stride = integer_zero_node;
860
861   tree ivvar = create_tmp_var (type, "graphite_IV");
862   tree iv, iv_after_increment;
863   loop_p loop = create_empty_loop_on_edge
864     (entry_edge, lb, stride, ub, ivvar, &iv, &iv_after_increment,
865      outer ? outer : entry_edge->src->loop_father);
866
867   isl_ast_expr *for_iterator = isl_ast_node_for_get_iterator (node_for);
868   isl_id *id = isl_ast_expr_get_id (for_iterator);
869   std::map<isl_id *, tree>::iterator res;
870   res = ip.find (id);
871   if (ip.count (id))
872     isl_id_free (res->first);
873   ip[id] = iv;
874   isl_ast_expr_free (for_iterator);
875   return loop;
876 }
877
878 /* Create the loop for a isl_ast_node_for.
879
880    - NEXT_E is the edge where new generated code should be attached.  */
881
882 edge
883 translate_isl_ast_to_gimple::
884 translate_isl_ast_for_loop (loop_p context_loop,
885                             __isl_keep isl_ast_node *node_for, edge next_e,
886                             tree type, tree lb, tree ub,
887                             ivs_params &ip)
888 {
889   gcc_assert (isl_ast_node_get_type (node_for) == isl_ast_node_for);
890   struct loop *loop = graphite_create_new_loop (next_e, node_for, context_loop,
891                                                 type, lb, ub, ip);
892   edge last_e = single_exit (loop);
893   edge to_body = single_succ_edge (loop->header);
894   basic_block after = to_body->dest;
895
896   /* Translate the body of the loop.  */
897   isl_ast_node *for_body = isl_ast_node_for_get_body (node_for);
898   next_e = translate_isl_ast (loop, for_body, to_body, ip);
899   isl_ast_node_free (for_body);
900
901   /* Early return if we failed to translate loop body.  */
902   if (!next_e || codegen_error_p ())
903     return NULL;
904
905   if (next_e->dest != after)
906     redirect_edge_succ_nodup (next_e, after);
907   set_immediate_dominator (CDI_DOMINATORS, next_e->dest, next_e->src);
908
909   if (flag_loop_parallelize_all)
910     {
911       isl_id *id = isl_ast_node_get_annotation (node_for);
912       gcc_assert (id);
913       ast_build_info *for_info = (ast_build_info *) isl_id_get_user (id);
914       loop->can_be_parallel = for_info->is_parallelizable;
915       free (for_info);
916       isl_id_free (id);
917     }
918
919   return last_e;
920 }
921
922 /* We use this function to get the upper bound because of the form,
923    which is used by isl to represent loops:
924
925    for (iterator = init; cond; iterator += inc)
926
927    {
928
929    ...
930
931    }
932
933    The loop condition is an arbitrary expression, which contains the
934    current loop iterator.
935
936    (e.g. iterator + 3 < B && C > iterator + A)
937
938    We have to know the upper bound of the iterator to generate a loop
939    in Gimple form. It can be obtained from the special representation
940    of the loop condition, which is generated by isl,
941    if the ast_build_atomic_upper_bound option is set. In this case,
942    isl generates a loop condition that consists of the current loop
943    iterator, + an operator (< or <=) and an expression not involving
944    the iterator, which is processed and returned by this function.
945
946    (e.g iterator <= upper-bound-expression-without-iterator)  */
947
948 static __isl_give isl_ast_expr *
949 get_upper_bound (__isl_keep isl_ast_node *node_for)
950 {
951   gcc_assert (isl_ast_node_get_type (node_for) == isl_ast_node_for);
952   isl_ast_expr *for_cond = isl_ast_node_for_get_cond (node_for);
953   gcc_assert (isl_ast_expr_get_type (for_cond) == isl_ast_expr_op);
954   isl_ast_expr *res;
955   switch (isl_ast_expr_get_op_type (for_cond))
956     {
957     case isl_ast_op_le:
958       res = isl_ast_expr_get_op_arg (for_cond, 1);
959       break;
960
961     case isl_ast_op_lt:
962       {
963         /* (iterator < ub) => (iterator <= ub - 1).  */
964         isl_val *one =
965           isl_val_int_from_si (isl_ast_expr_get_ctx (for_cond), 1);
966         isl_ast_expr *ub = isl_ast_expr_get_op_arg (for_cond, 1);
967         res = isl_ast_expr_sub (ub, isl_ast_expr_from_val (one));
968         break;
969       }
970
971     default:
972       gcc_unreachable ();
973     }
974   isl_ast_expr_free (for_cond);
975   return res;
976 }
977
978 /* All loops generated by create_empty_loop_on_edge have the form of
979    a post-test loop:
980
981    do
982
983    {
984      body of the loop;
985    } while (lower bound < upper bound);
986
987    We create a new if region protecting the loop to be executed, if
988    the execution count is zero (lower bound > upper bound).  */
989
990 edge
991 translate_isl_ast_to_gimple::
992 graphite_create_new_loop_guard (edge entry_edge,
993                                 __isl_keep isl_ast_node *node_for, tree *type,
994                                 tree *lb, tree *ub, ivs_params &ip)
995 {
996   gcc_assert (isl_ast_node_get_type (node_for) == isl_ast_node_for);
997   tree cond_expr;
998   edge exit_edge;
999
1000   *type =
1001     build_nonstandard_integer_type (graphite_expression_type_precision, 0);
1002   isl_ast_expr *for_init = isl_ast_node_for_get_init (node_for);
1003   *lb = gcc_expression_from_isl_expression (*type, for_init, ip);
1004   /* To fail code generation, we generate wrong code until we discard it.  */
1005   if (codegen_error)
1006     *lb = integer_zero_node;
1007   isl_ast_expr *upper_bound = get_upper_bound (node_for);
1008   *ub = gcc_expression_from_isl_expression (*type, upper_bound, ip);
1009   /* To fail code generation, we generate wrong code until we discard it.  */
1010   if (codegen_error)
1011     *ub = integer_zero_node;
1012   
1013   /* When ub is simply a constant or a parameter, use lb <= ub.  */
1014   if (TREE_CODE (*ub) == INTEGER_CST || TREE_CODE (*ub) == SSA_NAME)
1015     cond_expr = fold_build2 (LE_EXPR, boolean_type_node, *lb, *ub);
1016   else
1017     {
1018       tree one = (POINTER_TYPE_P (*type)
1019                   ? convert_to_ptrofftype (integer_one_node)
1020                   : fold_convert (*type, integer_one_node));
1021       /* Adding +1 and using LT_EXPR helps with loop latches that have a
1022          loop iteration count of "PARAMETER - 1".  For PARAMETER == 0 this
1023          becomes 2^k-1 due to integer overflow, and the condition lb <= ub
1024          is true, even if we do not want this.  However lb < ub + 1 is false,
1025          as expected.  */
1026       tree ub_one = fold_build2 (POINTER_TYPE_P (*type) ? POINTER_PLUS_EXPR
1027                                  : PLUS_EXPR, *type, *ub, one);
1028
1029       cond_expr = fold_build2 (LT_EXPR, boolean_type_node, *lb, ub_one);
1030     }
1031
1032   if (integer_onep (cond_expr))
1033     exit_edge = entry_edge;
1034   else
1035     exit_edge = create_empty_if_region_on_edge (entry_edge, cond_expr);
1036
1037   return exit_edge;
1038 }
1039
1040 /* Translates an isl_ast_node_for to Gimple. */
1041
1042 edge
1043 translate_isl_ast_to_gimple::
1044 translate_isl_ast_node_for (loop_p context_loop, __isl_keep isl_ast_node *node,
1045                             edge next_e, ivs_params &ip)
1046 {
1047   gcc_assert (isl_ast_node_get_type (node) == isl_ast_node_for);
1048   tree type, lb, ub;
1049   edge last_e = graphite_create_new_loop_guard (next_e, node, &type,
1050                                                 &lb, &ub, ip);
1051
1052   if (last_e == next_e)
1053     {
1054       /* There was no guard generated.  */
1055       last_e = single_succ_edge (split_edge (last_e));
1056
1057       translate_isl_ast_for_loop (context_loop, node, next_e,
1058                                   type, lb, ub, ip);
1059       return last_e;
1060     }
1061
1062   edge true_e = get_true_edge_from_guard_bb (next_e->dest);
1063   merge_points.safe_push (last_e);
1064
1065   last_e = single_succ_edge (split_edge (last_e));
1066   translate_isl_ast_for_loop (context_loop, node, true_e, type, lb, ub, ip);
1067
1068   return last_e;
1069 }
1070
1071 /* Inserts in iv_map a tuple (OLD_LOOP->num, NEW_NAME) for the induction
1072    variables of the loops around GBB in SESE.
1073  
1074    FIXME: Instead of using a vec<tree> that maps each loop id to a possible
1075    chrec, we could consider using a map<int, tree> that maps loop ids to the
1076    corresponding tree expressions.  */
1077
1078 void
1079 translate_isl_ast_to_gimple::
1080 build_iv_mapping (vec<tree> iv_map, gimple_poly_bb_p gbb,
1081                   __isl_keep isl_ast_expr *user_expr, ivs_params &ip,
1082                   sese_l &region)
1083 {
1084   gcc_assert (isl_ast_expr_get_type (user_expr) == isl_ast_expr_op &&
1085               isl_ast_expr_get_op_type (user_expr) == isl_ast_op_call);
1086   int i;
1087   isl_ast_expr *arg_expr;
1088   for (i = 1; i < isl_ast_expr_get_op_n_arg (user_expr); i++)
1089     {
1090       arg_expr = isl_ast_expr_get_op_arg (user_expr, i);
1091       tree type =
1092         build_nonstandard_integer_type (graphite_expression_type_precision, 0);
1093       tree t = gcc_expression_from_isl_expression (type, arg_expr, ip);
1094       /* To fail code generation, we generate wrong code until we discard it.  */
1095       if (codegen_error)
1096         t = integer_zero_node;
1097
1098       loop_p old_loop = gbb_loop_at_index (gbb, region, i - 1);
1099       iv_map[old_loop->num] = t;
1100     }
1101 }
1102
1103 /* Translates an isl_ast_node_user to Gimple.
1104
1105    FIXME: We should remove iv_map.create (loop->num + 1), if it is possible.  */
1106
1107 edge
1108 translate_isl_ast_to_gimple::
1109 translate_isl_ast_node_user (__isl_keep isl_ast_node *node,
1110                              edge next_e, ivs_params &ip)
1111 {
1112   gcc_assert (isl_ast_node_get_type (node) == isl_ast_node_user);
1113
1114   isl_ast_expr *user_expr = isl_ast_node_user_get_expr (node);
1115   isl_ast_expr *name_expr = isl_ast_expr_get_op_arg (user_expr, 0);
1116   gcc_assert (isl_ast_expr_get_type (name_expr) == isl_ast_expr_id);
1117
1118   isl_id *name_id = isl_ast_expr_get_id (name_expr);
1119   poly_bb_p pbb = (poly_bb_p) isl_id_get_user (name_id);
1120   gcc_assert (pbb);
1121
1122   gimple_poly_bb_p gbb = PBB_BLACK_BOX (pbb);
1123
1124   isl_ast_expr_free (name_expr);
1125   isl_id_free (name_id);
1126
1127   gcc_assert (GBB_BB (gbb) != ENTRY_BLOCK_PTR_FOR_FN (cfun) &&
1128               "The entry block should not even appear within a scop");
1129
1130   const int nb_loops = number_of_loops (cfun);
1131   vec<tree> iv_map;
1132   iv_map.create (nb_loops);
1133   iv_map.safe_grow_cleared (nb_loops);
1134
1135   build_iv_mapping (iv_map, gbb, user_expr, ip, pbb->scop->scop_info->region);
1136   isl_ast_expr_free (user_expr);
1137
1138   basic_block old_bb = GBB_BB (gbb);
1139   if (dump_file)
1140     {
1141       fprintf (dump_file,
1142                "[codegen] copying from bb_%d on edge (bb_%d, bb_%d)\n",
1143                old_bb->index, next_e->src->index, next_e->dest->index);
1144       print_loops_bb (dump_file, GBB_BB (gbb), 0, 3);
1145
1146     }
1147
1148   next_e = copy_bb_and_scalar_dependences (old_bb, next_e, iv_map);
1149
1150   iv_map.release ();
1151
1152   if (codegen_error_p ())
1153     return NULL;
1154
1155   if (dump_file)
1156     {
1157       fprintf (dump_file, "[codegen] (after copy) new basic block\n");
1158       print_loops_bb (dump_file, next_e->src, 0, 3);
1159     }
1160
1161   return next_e;
1162 }
1163
1164 /* Translates an isl_ast_node_block to Gimple. */
1165
1166 edge
1167 translate_isl_ast_to_gimple::
1168 translate_isl_ast_node_block (loop_p context_loop,
1169                               __isl_keep isl_ast_node *node,
1170                               edge next_e, ivs_params &ip)
1171 {
1172   gcc_assert (isl_ast_node_get_type (node) == isl_ast_node_block);
1173   isl_ast_node_list *node_list = isl_ast_node_block_get_children (node);
1174   int i;
1175   for (i = 0; i < isl_ast_node_list_n_ast_node (node_list); i++)
1176     {
1177       isl_ast_node *tmp_node = isl_ast_node_list_get_ast_node (node_list, i);
1178       next_e = translate_isl_ast (context_loop, tmp_node, next_e, ip);
1179       isl_ast_node_free (tmp_node);
1180     }
1181   isl_ast_node_list_free (node_list);
1182   return next_e;
1183 }
1184  
1185 /* Creates a new if region corresponding to isl's cond.  */
1186
1187 edge
1188 translate_isl_ast_to_gimple::
1189 graphite_create_new_guard (edge entry_edge, __isl_take isl_ast_expr *if_cond,
1190                            ivs_params &ip)
1191 {
1192   tree type =
1193     build_nonstandard_integer_type (graphite_expression_type_precision, 0);
1194   tree cond_expr = gcc_expression_from_isl_expression (type, if_cond, ip);
1195   /* To fail code generation, we generate wrong code until we discard it.  */
1196   if (codegen_error)
1197     cond_expr = integer_zero_node;
1198
1199   edge exit_edge = create_empty_if_region_on_edge (entry_edge, cond_expr);
1200   return exit_edge;
1201 }
1202
1203 /* Translates an isl_ast_node_if to Gimple.  */
1204
1205 edge
1206 translate_isl_ast_to_gimple::
1207 translate_isl_ast_node_if (loop_p context_loop,
1208                            __isl_keep isl_ast_node *node,
1209                            edge next_e, ivs_params &ip)
1210 {
1211   gcc_assert (isl_ast_node_get_type (node) == isl_ast_node_if);
1212   isl_ast_expr *if_cond = isl_ast_node_if_get_cond (node);
1213   edge last_e = graphite_create_new_guard (next_e, if_cond, ip);
1214   edge true_e = get_true_edge_from_guard_bb (next_e->dest);
1215   merge_points.safe_push (last_e);
1216
1217   isl_ast_node *then_node = isl_ast_node_if_get_then (node);
1218   translate_isl_ast (context_loop, then_node, true_e, ip);
1219   isl_ast_node_free (then_node);
1220
1221   edge false_e = get_false_edge_from_guard_bb (next_e->dest);
1222   isl_ast_node *else_node = isl_ast_node_if_get_else (node);
1223   if (isl_ast_node_get_type (else_node) != isl_ast_node_error)
1224     translate_isl_ast (context_loop, else_node, false_e, ip);
1225
1226   isl_ast_node_free (else_node);
1227   return last_e;
1228 }
1229
1230 /* Translates an isl AST node NODE to GCC representation in the
1231    context of a SESE.  */
1232
1233 edge
1234 translate_isl_ast_to_gimple::translate_isl_ast (loop_p context_loop,
1235                                                 __isl_keep isl_ast_node *node,
1236                                                 edge next_e, ivs_params &ip)
1237 {
1238   if (codegen_error_p ())
1239     return NULL;
1240
1241   switch (isl_ast_node_get_type (node))
1242     {
1243     case isl_ast_node_error:
1244       gcc_unreachable ();
1245
1246     case isl_ast_node_for:
1247       return translate_isl_ast_node_for (context_loop, node,
1248                                          next_e, ip);
1249
1250     case isl_ast_node_if:
1251       return translate_isl_ast_node_if (context_loop, node,
1252                                         next_e, ip);
1253
1254     case isl_ast_node_user:
1255       return translate_isl_ast_node_user (node, next_e, ip);
1256
1257     case isl_ast_node_block:
1258       return translate_isl_ast_node_block (context_loop, node,
1259                                            next_e, ip);
1260
1261 #ifdef HAVE_ISL_OPTIONS_SET_SCHEDULE_SERIALIZE_SCCS
1262     case isl_ast_node_mark:
1263       {
1264         isl_ast_node *n = isl_ast_node_mark_get_node (node);
1265         edge e = translate_isl_ast (context_loop, n, next_e, ip);
1266         isl_ast_node_free (n);
1267         return e;
1268       }
1269 #endif
1270
1271     default:
1272       gcc_unreachable ();
1273     }
1274 }
1275
1276 /* Return true when BB contains loop close phi nodes.  A loop close phi node is
1277    at the exit of loop which takes one argument that is the last value of the
1278    variable being used out of the loop.  */
1279
1280 static bool
1281 bb_contains_loop_close_phi_nodes (basic_block bb)
1282 {
1283   return single_pred_p (bb)
1284     && bb->loop_father != single_pred_edge (bb)->src->loop_father;
1285 }
1286
1287 /* Return true when BB contains loop phi nodes.  A loop phi node is the loop
1288    header containing phi nodes which has one init-edge and one back-edge.  */
1289
1290 static bool
1291 bb_contains_loop_phi_nodes (basic_block bb)
1292 {
1293   gcc_assert (EDGE_COUNT (bb->preds) <= 2);
1294
1295   if (bb->preds->length () == 1)
1296     return false;
1297
1298   unsigned depth = loop_depth (bb->loop_father);
1299
1300   edge preds[2] = { (*bb->preds)[0], (*bb->preds)[1] };
1301
1302   if (depth > loop_depth (preds[0]->src->loop_father)
1303       || depth > loop_depth (preds[1]->src->loop_father))
1304     return true;
1305
1306   /* When one of the edges correspond to the same loop father and other
1307      doesn't.  */
1308   if (bb->loop_father != preds[0]->src->loop_father
1309       && bb->loop_father == preds[1]->src->loop_father)
1310     return true;
1311
1312   if (bb->loop_father != preds[1]->src->loop_father
1313       && bb->loop_father == preds[0]->src->loop_father)
1314     return true;
1315
1316   return false;
1317 }
1318
1319 /* Check if USE is defined in a basic block from where the definition of USE can
1320    propagate from all the paths.  FIXME: Verify checks for virtual operands.  */
1321
1322 static bool
1323 is_loop_closed_ssa_use (basic_block bb, tree use)
1324 {
1325   if (TREE_CODE (use) != SSA_NAME || virtual_operand_p (use))
1326     return true;
1327
1328   /* For close-phi nodes def always comes from a loop which has a back-edge.  */
1329   if (bb_contains_loop_close_phi_nodes (bb))
1330     return true;
1331
1332   gimple *def = SSA_NAME_DEF_STMT (use);
1333   basic_block def_bb = gimple_bb (def);
1334   return (!def_bb
1335           || flow_bb_inside_loop_p (def_bb->loop_father, bb));
1336 }
1337
1338 /* Return the number of phi nodes in BB.  */
1339
1340 static int
1341 number_of_phi_nodes (basic_block bb)
1342 {
1343   int num_phis = 0;
1344   for (gphi_iterator psi = gsi_start_phis (bb); !gsi_end_p (psi);
1345        gsi_next (&psi))
1346     num_phis++;
1347   return num_phis;
1348 }
1349
1350 /* Returns true if BB uses name in one of its PHIs.  */
1351
1352 static bool
1353 phi_uses_name (basic_block bb, tree name)
1354 {
1355   for (gphi_iterator psi = gsi_start_phis (bb); !gsi_end_p (psi);
1356        gsi_next (&psi))
1357     {
1358       gphi *phi = psi.phi ();
1359       for (unsigned i = 0; i < gimple_phi_num_args (phi); i++)
1360         {
1361           tree use_arg = gimple_phi_arg_def (phi, i);
1362           if (use_arg == name)
1363             return true;
1364         }
1365     }
1366   return false;
1367 }
1368
1369 /* Return true if RENAME (defined in BB) is a valid use in NEW_BB.  The
1370    definition should flow into use, and the use should respect the loop-closed
1371    SSA form.  */
1372
1373 bool
1374 translate_isl_ast_to_gimple::
1375 is_valid_rename (tree rename, basic_block def_bb, basic_block use_bb,
1376                  bool loop_phi, tree old_name, basic_block old_bb) const
1377 {
1378   /* The def of the rename must either dominate the uses or come from a
1379      back-edge.  Also the def must respect the loop closed ssa form.  */
1380   if (!is_loop_closed_ssa_use (use_bb, rename))
1381     {
1382       if (dump_file)
1383         {
1384           fprintf (dump_file, "[codegen] rename not in loop closed ssa:");
1385           print_generic_expr (dump_file, rename, 0);
1386           fprintf (dump_file, "\n");
1387         }
1388       return false;
1389     }
1390
1391   if (dominated_by_p (CDI_DOMINATORS, use_bb, def_bb))
1392     return true;
1393
1394   if (bb_contains_loop_phi_nodes (use_bb) && loop_phi)
1395     {
1396       /* The loop-header dominates the loop-body.  */
1397       if (!dominated_by_p (CDI_DOMINATORS, def_bb, use_bb))
1398         return false;
1399
1400       /* RENAME would be used in loop-phi.  */
1401       gcc_assert (number_of_phi_nodes (use_bb));
1402
1403       /* For definitions coming from back edges, we should check that
1404          old_name is used in a loop PHI node.
1405          FIXME: Verify if this is true.  */
1406       if (phi_uses_name (old_bb, old_name))
1407         return true;
1408     }
1409   return false;
1410 }
1411
1412 /* Returns the expression associated to OLD_NAME (which is used in OLD_BB), in
1413    NEW_BB from RENAME_MAP.  LOOP_PHI is true when we want to rename OLD_NAME
1414    within a loop PHI instruction.  */
1415
1416 tree
1417 translate_isl_ast_to_gimple::get_rename (basic_block new_bb,
1418                                          tree old_name,
1419                                          basic_block old_bb,
1420                                          bool loop_phi) const
1421 {
1422   gcc_assert (TREE_CODE (old_name) == SSA_NAME);
1423   vec <tree> *renames = region->rename_map->get (old_name);
1424
1425   if (!renames || renames->is_empty ())
1426     return NULL_TREE;
1427
1428   if (1 == renames->length ())
1429     {
1430       tree rename = (*renames)[0];
1431       if (TREE_CODE (rename) == SSA_NAME)
1432         {
1433           basic_block bb = gimple_bb (SSA_NAME_DEF_STMT (rename));
1434           if (is_valid_rename (rename, bb, new_bb, loop_phi, old_name, old_bb))
1435             return rename;
1436           return NULL_TREE;
1437         }
1438
1439       if (is_constant (rename))
1440         return rename;
1441
1442       return NULL_TREE;
1443     }
1444
1445   /* More than one renames corresponding to the old_name.  Find the rename for
1446      which the definition flows into usage at new_bb.  */
1447   int i;
1448   tree t1 = NULL_TREE, t2;
1449   basic_block t1_bb = NULL;
1450   FOR_EACH_VEC_ELT (*renames, i, t2)
1451     {
1452       basic_block t2_bb = gimple_bb (SSA_NAME_DEF_STMT (t2));
1453
1454       /* Defined in the same basic block as used.  */
1455       if (t2_bb == new_bb)
1456         return t2;
1457
1458       /* NEW_BB and T2_BB are in two unrelated if-clauses.  */
1459       if (!dominated_by_p (CDI_DOMINATORS, new_bb, t2_bb))
1460         continue;
1461
1462       /* Compute the nearest dominator.  */
1463       if (!t1 || dominated_by_p (CDI_DOMINATORS, t2_bb, t1_bb))
1464         {
1465           t1_bb = t2_bb;
1466           t1 = t2;
1467         }
1468     }
1469
1470   return t1;
1471 }
1472
1473 /* Register in RENAME_MAP the rename tuple (OLD_NAME, EXPR).
1474    When OLD_NAME and EXPR are the same we assert.  */
1475
1476 void
1477 translate_isl_ast_to_gimple::set_rename (tree old_name, tree expr)
1478 {
1479   if (dump_file)
1480     {
1481       fprintf (dump_file, "[codegen] setting rename: old_name = ");
1482       print_generic_expr (dump_file, old_name, 0);
1483       fprintf (dump_file, ", new_name = ");
1484       print_generic_expr (dump_file, expr, 0);
1485       fprintf (dump_file, "\n");
1486     }
1487
1488   if (old_name == expr)
1489     return;
1490
1491   vec <tree> *renames = region->rename_map->get (old_name);
1492
1493   if (renames)
1494     renames->safe_push (expr);
1495   else
1496     {
1497       vec<tree> r;
1498       r.create (2);
1499       r.safe_push (expr);
1500       region->rename_map->put (old_name, r);
1501     }
1502
1503   tree t;
1504   int i;
1505   /* For a parameter of a scop we don't want to rename it.  */
1506   FOR_EACH_VEC_ELT (region->params, i, t)
1507     if (old_name == t)
1508       region->parameter_rename_map->put(old_name, expr);
1509 }
1510
1511 /* Return an iterator to the instructions comes last in the execution order.
1512    Either GSI1 and GSI2 should belong to the same basic block or one of their
1513    respective basic blocks should dominate the other.  */
1514
1515 gimple_stmt_iterator
1516 later_of_the_two (gimple_stmt_iterator gsi1, gimple_stmt_iterator gsi2)
1517 {
1518   basic_block bb1 = gsi_bb (gsi1);
1519   basic_block bb2 = gsi_bb (gsi2);
1520
1521   /* Find the iterator which is the latest.  */
1522   if (bb1 == bb2)
1523     {
1524       /* For empty basic blocks gsis point to the end of the sequence.  Since
1525          there is no operator== defined for gimple_stmt_iterator and for gsis
1526          not pointing to a valid statement gsi_next would assert.  */
1527       gimple_stmt_iterator gsi = gsi1;
1528       do {
1529         if (gsi_stmt (gsi) == gsi_stmt (gsi2))
1530           return gsi2;
1531         gsi_next (&gsi);
1532       } while (!gsi_end_p (gsi));
1533
1534       return gsi1;
1535     }
1536
1537   /* Find the basic block closest to the basic block which defines stmt.  */
1538   if (dominated_by_p (CDI_DOMINATORS, bb1, bb2))
1539     return gsi1;
1540
1541   gcc_assert (dominated_by_p (CDI_DOMINATORS, bb2, bb1));
1542   return gsi2;
1543 }
1544
1545 /* Insert each statement from SEQ at its earliest insertion p.  */
1546
1547 void
1548 translate_isl_ast_to_gimple::gsi_insert_earliest (gimple_seq seq)
1549 {
1550   update_modified_stmts (seq);
1551   sese_l &codegen_region = region->if_region->true_region->region;
1552   basic_block begin_bb = get_entry_bb (codegen_region);
1553
1554   /* Inserting the gimple statements in a vector because gimple_seq behave
1555      in strage ways when inserting the stmts from it into different basic
1556      blocks one at a time.  */
1557   auto_vec<gimple *, 3> stmts;
1558   for (gimple_stmt_iterator gsi = gsi_start (seq); !gsi_end_p (gsi);
1559        gsi_next (&gsi))
1560     stmts.safe_push (gsi_stmt (gsi));
1561
1562   int i;
1563   gimple *use_stmt;
1564   FOR_EACH_VEC_ELT (stmts, i, use_stmt)
1565     {
1566       gcc_assert (gimple_code (use_stmt) != GIMPLE_PHI);
1567       gimple_stmt_iterator gsi_def_stmt = gsi_start_bb_nondebug (begin_bb);
1568
1569       use_operand_p use_p;
1570       ssa_op_iter op_iter;
1571       FOR_EACH_SSA_USE_OPERAND (use_p, use_stmt, op_iter, SSA_OP_USE)
1572         {
1573           /* Iterator to the current def of use_p.  For function parameters or
1574              anything where def is not found, insert at the beginning of the
1575              generated region.  */
1576           gimple_stmt_iterator gsi_stmt = gsi_def_stmt;
1577
1578           tree op = USE_FROM_PTR (use_p);
1579           gimple *stmt = SSA_NAME_DEF_STMT (op);
1580           if (stmt && (gimple_code (stmt) != GIMPLE_NOP))
1581             gsi_stmt = gsi_for_stmt (stmt);
1582
1583           /* For region parameters, insert at the beginning of the generated
1584              region.  */
1585           if (!bb_in_sese_p (gsi_bb (gsi_stmt), codegen_region))
1586             gsi_stmt = gsi_def_stmt;
1587
1588           gsi_def_stmt = later_of_the_two (gsi_stmt, gsi_def_stmt);
1589         }
1590
1591       if (!gsi_stmt (gsi_def_stmt))
1592         {
1593           gimple_stmt_iterator gsi = gsi_after_labels (gsi_bb (gsi_def_stmt));
1594           gsi_insert_before (&gsi, use_stmt, GSI_NEW_STMT);
1595         }
1596       else if (gimple_code (gsi_stmt (gsi_def_stmt)) == GIMPLE_PHI)
1597         {
1598           gimple_stmt_iterator bsi
1599             = gsi_start_bb_nondebug (gsi_bb (gsi_def_stmt));
1600           /* Insert right after the PHI statements.  */
1601           gsi_insert_before (&bsi, use_stmt, GSI_NEW_STMT);
1602         }
1603       else
1604         gsi_insert_after (&gsi_def_stmt, use_stmt, GSI_NEW_STMT);
1605
1606       if (dump_file)
1607         {
1608           fprintf (dump_file, "[codegen] inserting statement: ");
1609           print_gimple_stmt (dump_file, use_stmt, 0, TDF_VOPS | TDF_MEMSYMS);
1610           print_loops_bb (dump_file, gimple_bb (use_stmt), 0, 3);
1611         }
1612     }
1613 }
1614
1615 /* Collect all the operands of NEW_EXPR by recursively visiting each
1616    operand.  */
1617
1618 void
1619 translate_isl_ast_to_gimple::collect_all_ssa_names (tree new_expr,
1620                                                     vec<tree> *vec_ssa)
1621 {
1622
1623   /* Rename all uses in new_expr.  */
1624   if (TREE_CODE (new_expr) == SSA_NAME)
1625     {
1626       vec_ssa->safe_push (new_expr);
1627       return;
1628     }
1629
1630   /* Iterate over SSA_NAMES in NEW_EXPR.  */
1631   for (int i = 0; i < (TREE_CODE_LENGTH (TREE_CODE (new_expr))); i++)
1632     {
1633       tree op = TREE_OPERAND (new_expr, i);
1634       collect_all_ssa_names (op, vec_ssa);
1635     }
1636 }
1637
1638 /* This is abridged version of the function copied from:
1639    tree.c:substitute_in_expr (tree exp, tree f, tree r).  */
1640
1641 static tree
1642 substitute_ssa_name (tree exp, tree f, tree r)
1643 {
1644   enum tree_code code = TREE_CODE (exp);
1645   tree op0, op1, op2, op3;
1646   tree new_tree;
1647
1648   /* We handle TREE_LIST and COMPONENT_REF separately.  */
1649   if (code == TREE_LIST)
1650     {
1651       op0 = substitute_ssa_name (TREE_CHAIN (exp), f, r);
1652       op1 = substitute_ssa_name (TREE_VALUE (exp), f, r);
1653       if (op0 == TREE_CHAIN (exp) && op1 == TREE_VALUE (exp))
1654         return exp;
1655
1656       return tree_cons (TREE_PURPOSE (exp), op1, op0);
1657     }
1658   else if (code == COMPONENT_REF)
1659     {
1660       tree inner;
1661
1662       /* If this expression is getting a value from a PLACEHOLDER_EXPR
1663          and it is the right field, replace it with R.  */
1664       for (inner = TREE_OPERAND (exp, 0);
1665            REFERENCE_CLASS_P (inner);
1666            inner = TREE_OPERAND (inner, 0))
1667         ;
1668
1669       /* The field.  */
1670       op1 = TREE_OPERAND (exp, 1);
1671
1672       if (TREE_CODE (inner) == PLACEHOLDER_EXPR && op1 == f)
1673         return r;
1674
1675       /* If this expression hasn't been completed let, leave it alone.  */
1676       if (TREE_CODE (inner) == PLACEHOLDER_EXPR && !TREE_TYPE (inner))
1677         return exp;
1678
1679       op0 = substitute_ssa_name (TREE_OPERAND (exp, 0), f, r);
1680       if (op0 == TREE_OPERAND (exp, 0))
1681         return exp;
1682
1683       new_tree
1684         = fold_build3 (COMPONENT_REF, TREE_TYPE (exp), op0, op1, NULL_TREE);
1685     }
1686   else
1687     switch (TREE_CODE_CLASS (code))
1688       {
1689       case tcc_constant:
1690         return exp;
1691
1692       case tcc_declaration:
1693         if (exp == f)
1694           return r;
1695         else
1696           return exp;
1697
1698       case tcc_expression:
1699         if (exp == f)
1700           return r;
1701
1702         /* Fall through...  */
1703
1704       case tcc_exceptional:
1705       case tcc_unary:
1706       case tcc_binary:
1707       case tcc_comparison:
1708       case tcc_reference:
1709         switch (TREE_CODE_LENGTH (code))
1710           {
1711           case 0:
1712             if (exp == f)
1713               return r;
1714             return exp;
1715
1716           case 1:
1717             op0 = substitute_ssa_name (TREE_OPERAND (exp, 0), f, r);
1718             if (op0 == TREE_OPERAND (exp, 0))
1719               return exp;
1720
1721             new_tree = fold_build1 (code, TREE_TYPE (exp), op0);
1722             break;
1723
1724           case 2:
1725             op0 = substitute_ssa_name (TREE_OPERAND (exp, 0), f, r);
1726             op1 = substitute_ssa_name (TREE_OPERAND (exp, 1), f, r);
1727
1728             if (op0 == TREE_OPERAND (exp, 0) && op1 == TREE_OPERAND (exp, 1))
1729               return exp;
1730
1731             new_tree = fold_build2 (code, TREE_TYPE (exp), op0, op1);
1732             break;
1733
1734           case 3:
1735             op0 = substitute_ssa_name (TREE_OPERAND (exp, 0), f, r);
1736             op1 = substitute_ssa_name (TREE_OPERAND (exp, 1), f, r);
1737             op2 = substitute_ssa_name (TREE_OPERAND (exp, 2), f, r);
1738
1739             if (op0 == TREE_OPERAND (exp, 0) && op1 == TREE_OPERAND (exp, 1)
1740                 && op2 == TREE_OPERAND (exp, 2))
1741               return exp;
1742
1743             new_tree = fold_build3 (code, TREE_TYPE (exp), op0, op1, op2);
1744             break;
1745
1746           case 4:
1747             op0 = substitute_ssa_name (TREE_OPERAND (exp, 0), f, r);
1748             op1 = substitute_ssa_name (TREE_OPERAND (exp, 1), f, r);
1749             op2 = substitute_ssa_name (TREE_OPERAND (exp, 2), f, r);
1750             op3 = substitute_ssa_name (TREE_OPERAND (exp, 3), f, r);
1751
1752             if (op0 == TREE_OPERAND (exp, 0) && op1 == TREE_OPERAND (exp, 1)
1753                 && op2 == TREE_OPERAND (exp, 2)
1754                 && op3 == TREE_OPERAND (exp, 3))
1755               return exp;
1756
1757             new_tree
1758               = fold (build4 (code, TREE_TYPE (exp), op0, op1, op2, op3));
1759             break;
1760
1761           default:
1762             gcc_unreachable ();
1763           }
1764         break;
1765
1766       case tcc_vl_exp:
1767       default:
1768         gcc_unreachable ();
1769       }
1770
1771   TREE_READONLY (new_tree) |= TREE_READONLY (exp);
1772
1773   if (code == INDIRECT_REF || code == ARRAY_REF || code == ARRAY_RANGE_REF)
1774     TREE_THIS_NOTRAP (new_tree) |= TREE_THIS_NOTRAP (exp);
1775
1776   return new_tree;
1777 }
1778
1779 /* Rename all the operands of NEW_EXPR by recursively visiting each operand.  */
1780
1781 tree
1782 translate_isl_ast_to_gimple::rename_all_uses (tree new_expr, basic_block new_bb,
1783                                               basic_block old_bb)
1784 {
1785   auto_vec<tree, 2> ssa_names;
1786   collect_all_ssa_names (new_expr, &ssa_names);
1787   tree t;
1788   int i;
1789   FOR_EACH_VEC_ELT (ssa_names, i, t)
1790     if (tree r = get_rename (new_bb, t, old_bb, false))
1791       new_expr = substitute_ssa_name (new_expr, t, r);
1792
1793   return new_expr;
1794 }
1795
1796 /* For ops which are scev_analyzeable, we can regenerate a new name from its
1797    scalar evolution around LOOP.  */
1798
1799 tree
1800 translate_isl_ast_to_gimple::
1801 get_rename_from_scev (tree old_name, gimple_seq *stmts, loop_p loop,
1802                       basic_block new_bb, basic_block old_bb,
1803                       vec<tree> iv_map)
1804 {
1805   tree scev = scalar_evolution_in_region (region->region, loop, old_name);
1806
1807   /* At this point we should know the exact scev for each
1808      scalar SSA_NAME used in the scop: all the other scalar
1809      SSA_NAMEs should have been translated out of SSA using
1810      arrays with one element.  */
1811   tree new_expr;
1812   if (chrec_contains_undetermined (scev))
1813     {
1814       codegen_error = true;
1815       return build_zero_cst (TREE_TYPE (old_name));
1816     }
1817
1818   new_expr = chrec_apply_map (scev, iv_map);
1819
1820   /* The apply should produce an expression tree containing
1821      the uses of the new induction variables.  We should be
1822      able to use new_expr instead of the old_name in the newly
1823      generated loop nest.  */
1824   if (chrec_contains_undetermined (new_expr)
1825       || tree_contains_chrecs (new_expr, NULL))
1826     {
1827       codegen_error = true;
1828       return build_zero_cst (TREE_TYPE (old_name));
1829     }
1830
1831   /* We should check all the operands and all of them should dominate the use at
1832      new_expr.  */
1833   if (TREE_CODE (new_expr) == SSA_NAME)
1834     {
1835       basic_block bb = gimple_bb (SSA_NAME_DEF_STMT (new_expr));
1836       if (bb && !dominated_by_p (CDI_DOMINATORS, new_bb, bb))
1837         {
1838           codegen_error = true;
1839           return build_zero_cst (TREE_TYPE (old_name));
1840         }
1841     }
1842
1843   new_expr = rename_all_uses (new_expr, new_bb, old_bb);
1844
1845   /* We check all the operands and all of them should dominate the use at
1846      new_expr.  */
1847   auto_vec <tree, 2> new_ssa_names;
1848   collect_all_ssa_names (new_expr, &new_ssa_names);
1849   int i;
1850   tree new_ssa_name;
1851   FOR_EACH_VEC_ELT (new_ssa_names, i, new_ssa_name)
1852     {
1853       if (TREE_CODE (new_ssa_name) == SSA_NAME)
1854         {
1855           basic_block bb = gimple_bb (SSA_NAME_DEF_STMT (new_ssa_name));
1856           if (bb && !dominated_by_p (CDI_DOMINATORS, new_bb, bb))
1857             {
1858               codegen_error = true;
1859               return build_zero_cst (TREE_TYPE (old_name));
1860             }
1861         }
1862     }
1863
1864   /* Replace the old_name with the new_expr.  */
1865   return force_gimple_operand (unshare_expr (new_expr), stmts,
1866                                true, NULL_TREE);
1867 }
1868
1869 /* Renames the scalar uses of the statement COPY, using the
1870    substitution map RENAME_MAP, inserting the gimplification code at
1871    GSI_TGT, for the translation REGION, with the original copied
1872    statement in LOOP, and using the induction variable renaming map
1873    IV_MAP.  Returns true when something has been renamed.  codegen_error
1874    is set when the code generation cannot continue.  */
1875
1876 bool
1877 translate_isl_ast_to_gimple::rename_uses (gimple *copy,
1878                                           gimple_stmt_iterator *gsi_tgt,
1879                                           basic_block old_bb,
1880                                           loop_p loop, vec<tree> iv_map)
1881 {
1882   bool changed = false;
1883
1884   if (is_gimple_debug (copy))
1885     {
1886       if (gimple_debug_bind_p (copy))
1887         gimple_debug_bind_reset_value (copy);
1888       else if (gimple_debug_source_bind_p (copy))
1889         return false;
1890       else
1891         gcc_unreachable ();
1892
1893       return false;
1894     }
1895
1896   if (dump_file)
1897     {
1898       fprintf (dump_file, "[codegen] renaming uses of stmt: ");
1899       print_gimple_stmt (dump_file, copy, 0, 0);
1900     }
1901
1902   use_operand_p use_p;
1903   ssa_op_iter op_iter;
1904   FOR_EACH_SSA_USE_OPERAND (use_p, copy, op_iter, SSA_OP_USE)
1905     {
1906       tree old_name = USE_FROM_PTR (use_p);
1907
1908       if (dump_file)
1909         {
1910           fprintf (dump_file, "[codegen] renaming old_name = ");
1911           print_generic_expr (dump_file, old_name, 0);
1912           fprintf (dump_file, "\n");
1913         }
1914
1915       if (TREE_CODE (old_name) != SSA_NAME
1916           || SSA_NAME_IS_DEFAULT_DEF (old_name))
1917         continue;
1918
1919       changed = true;
1920       tree new_expr = get_rename (gsi_tgt->bb, old_name,
1921                                   old_bb, false);
1922
1923       if (new_expr)
1924         {
1925           tree type_old_name = TREE_TYPE (old_name);
1926           tree type_new_expr = TREE_TYPE (new_expr);
1927
1928           if (dump_file)
1929             {
1930               fprintf (dump_file, "[codegen] from rename_map: new_name = ");
1931               print_generic_expr (dump_file, new_expr, 0);
1932               fprintf (dump_file, "\n");
1933             }
1934
1935           if (type_old_name != type_new_expr
1936               || TREE_CODE (new_expr) != SSA_NAME)
1937             {
1938               tree var = create_tmp_var (type_old_name, "var");
1939
1940               if (!useless_type_conversion_p (type_old_name, type_new_expr))
1941                 new_expr = fold_convert (type_old_name, new_expr);
1942
1943               gimple_seq stmts;
1944               new_expr = force_gimple_operand (new_expr, &stmts, true, var);
1945               gsi_insert_earliest (stmts);
1946             }
1947
1948           replace_exp (use_p, new_expr);
1949           continue;
1950         }
1951
1952       gimple_seq stmts;
1953       new_expr = get_rename_from_scev (old_name, &stmts, loop, gimple_bb (copy),
1954                                        old_bb, iv_map);
1955       if (!new_expr || codegen_error_p ())
1956         return false;
1957
1958       if (dump_file)
1959         {
1960           fprintf (dump_file, "[codegen] not in rename map, scev: ");
1961           print_generic_expr (dump_file, new_expr, 0);
1962           fprintf (dump_file, "\n");
1963         }
1964
1965       gsi_insert_earliest (stmts);
1966       replace_exp (use_p, new_expr);
1967
1968       if (TREE_CODE (new_expr) == INTEGER_CST
1969           && is_gimple_assign (copy))
1970         {
1971           tree rhs = gimple_assign_rhs1 (copy);
1972
1973           if (TREE_CODE (rhs) == ADDR_EXPR)
1974             recompute_tree_invariant_for_addr_expr (rhs);
1975         }
1976
1977       set_rename (old_name, new_expr);
1978     }
1979
1980   return changed;
1981 }
1982
1983 /* Returns a basic block that could correspond to where a constant was defined
1984    in the original code.  In the original code OLD_BB had the definition, we
1985    need to find which basic block out of the copies of old_bb, in the new
1986    region, should a definition correspond to if it has to reach BB.  */
1987
1988 basic_block
1989 translate_isl_ast_to_gimple::get_def_bb_for_const (basic_block bb,
1990                                                    basic_block old_bb) const
1991 {
1992   vec <basic_block> *bbs = region->copied_bb_map->get (old_bb);
1993
1994   if (!bbs || bbs->is_empty ())
1995     return NULL;
1996
1997   if (1 == bbs->length ())
1998     return (*bbs)[0];
1999
2000   int i;
2001   basic_block b1 = NULL, b2;
2002   FOR_EACH_VEC_ELT (*bbs, i, b2)
2003     {
2004       if (b2 == bb)
2005         return bb;
2006
2007       /* BB and B2 are in two unrelated if-clauses.  */
2008       if (!dominated_by_p (CDI_DOMINATORS, bb, b2))
2009         continue;
2010
2011       /* Compute the nearest dominator.  */
2012       if (!b1 || dominated_by_p (CDI_DOMINATORS, b2, b1))
2013         b1 = b2;
2014     }
2015
2016   gcc_assert (b1);
2017   return b1;
2018 }
2019
2020 /* Get the new name of OP (from OLD_BB) to be used in NEW_BB.  LOOP_PHI is true
2021    when we want to rename an OP within a loop PHI instruction.  */
2022
2023 tree
2024 translate_isl_ast_to_gimple::
2025 get_new_name (basic_block new_bb, tree op,
2026               basic_block old_bb, bool loop_phi) const
2027 {
2028   /* For constants the names are the same.  */
2029   if (is_constant (op))
2030     return op;
2031
2032   return get_rename (new_bb, op, old_bb, loop_phi);
2033 }
2034
2035 /* Return a debug location for OP.  */
2036
2037 static location_t
2038 get_loc (tree op)
2039 {
2040   location_t loc = UNKNOWN_LOCATION;
2041
2042   if (TREE_CODE (op) == SSA_NAME)
2043     loc = gimple_location (SSA_NAME_DEF_STMT (op));
2044   return loc;
2045 }
2046
2047 /* Returns the incoming edges of basic_block BB in the pair.  The first edge is
2048    the init edge (from outside the loop) and the second one is the back edge
2049    from the same loop.  */
2050
2051 std::pair<edge, edge>
2052 get_edges (basic_block bb)
2053 {
2054   std::pair<edge, edge> edges;
2055   edge e;
2056   edge_iterator ei;
2057   FOR_EACH_EDGE (e, ei, bb->preds)
2058     if (bb->loop_father != e->src->loop_father)
2059       edges.first = e;
2060     else
2061       edges.second = e;
2062   return edges;
2063 }
2064
2065 /* Copy the PHI arguments from OLD_PHI to the NEW_PHI.  The arguments to NEW_PHI
2066    must be found unless they can be POSTPONEd for later.  */
2067
2068 bool
2069 translate_isl_ast_to_gimple::
2070 copy_loop_phi_args (gphi *old_phi, init_back_edge_pair_t &ibp_old_bb,
2071                     gphi *new_phi, init_back_edge_pair_t &ibp_new_bb,
2072                     bool postpone)
2073 {
2074   gcc_assert (gimple_phi_num_args (old_phi) == gimple_phi_num_args (new_phi));
2075
2076   basic_block new_bb = gimple_bb (new_phi);
2077   for (unsigned i = 0; i < gimple_phi_num_args (old_phi); i++)
2078     {
2079       edge e;
2080       if (gimple_phi_arg_edge (old_phi, i) == ibp_old_bb.first)
2081         e = ibp_new_bb.first;
2082       else
2083         e = ibp_new_bb.second;
2084
2085       tree old_name = gimple_phi_arg_def (old_phi, i);
2086       tree new_name = get_new_name (new_bb, old_name,
2087                                     gimple_bb (old_phi), true);
2088       if (new_name)
2089         {
2090           add_phi_arg (new_phi, new_name, e, get_loc (old_name));
2091           continue;
2092         }
2093
2094       gimple *old_def_stmt = SSA_NAME_DEF_STMT (old_name);
2095       if (!old_def_stmt || gimple_code (old_def_stmt) == GIMPLE_NOP)
2096         /* If the phi arg was a function arg, or wasn't defined, just use the
2097            old name.  */
2098         add_phi_arg (new_phi, old_name, e, get_loc (old_name));
2099       else if (postpone)
2100         {
2101           /* Postpone code gen for later for those back-edges we don't have the
2102              names yet.  */
2103           region->incomplete_phis.safe_push (std::make_pair (old_phi, new_phi));
2104           if (dump_file)
2105             fprintf (dump_file, "[codegen] postpone loop phi nodes.\n");
2106         }
2107       else
2108         /* Either we should add the arg to phi or, we should postpone.  */
2109         return false;
2110     }
2111   return true;
2112 }
2113
2114 /* Copy loop phi nodes from BB to NEW_BB.  */
2115
2116 bool
2117 translate_isl_ast_to_gimple::copy_loop_phi_nodes (basic_block bb,
2118                                                   basic_block new_bb)
2119 {
2120   if (dump_file)
2121     fprintf (dump_file, "[codegen] copying loop phi nodes in bb_%d.\n",
2122              new_bb->index);
2123
2124   /* Loop phi nodes should have only two arguments.  */
2125   gcc_assert (2 == EDGE_COUNT (bb->preds));
2126
2127   /* First edge is the init edge and second is the back edge.  */
2128   init_back_edge_pair_t ibp_old_bb = get_edges (bb);
2129
2130   /* First edge is the init edge and second is the back edge.  */
2131   init_back_edge_pair_t ibp_new_bb = get_edges (new_bb);
2132
2133   for (gphi_iterator psi = gsi_start_phis (bb); !gsi_end_p (psi);
2134        gsi_next (&psi))
2135     {
2136       gphi *phi = psi.phi ();
2137       tree res = gimple_phi_result (phi);
2138       if (virtual_operand_p (res))
2139         continue;
2140       if (is_gimple_reg (res) && scev_analyzable_p (res, region->region))
2141         continue;
2142
2143       gphi *new_phi = create_phi_node (SSA_NAME_VAR (res), new_bb);
2144       tree new_res = create_new_def_for (res, new_phi,
2145                                          gimple_phi_result_ptr (new_phi));
2146       set_rename (res, new_res);
2147       codegen_error = !copy_loop_phi_args (phi, ibp_old_bb, new_phi,
2148                                           ibp_new_bb, true);
2149       update_stmt (new_phi);
2150
2151       if (dump_file)
2152         {
2153           fprintf (dump_file, "[codegen] creating loop-phi node: ");
2154           print_gimple_stmt (dump_file, new_phi, 0, 0);
2155         }
2156     }
2157
2158   return true;
2159 }
2160
2161 /* Return the init value of PHI, the value coming from outside the loop.  */
2162
2163 static tree
2164 get_loop_init_value (gphi *phi)
2165 {
2166
2167   loop_p loop = gimple_bb (phi)->loop_father;
2168
2169   edge e;
2170   edge_iterator ei;
2171   FOR_EACH_EDGE (e, ei, gimple_bb (phi)->preds)
2172     if (e->src->loop_father != loop)
2173       return gimple_phi_arg_def (phi, e->dest_idx);
2174
2175   return NULL_TREE;
2176 }
2177
2178 /* Find the init value (the value which comes from outside the loop), of one of
2179    the operands of DEF which is defined by a loop phi.  */
2180
2181 static tree
2182 find_init_value (gimple *def)
2183 {
2184   if (gimple_code (def) == GIMPLE_PHI)
2185     return get_loop_init_value (as_a <gphi*> (def));
2186
2187   if (gimple_vuse (def))
2188     return NULL_TREE;
2189
2190   ssa_op_iter iter;
2191   use_operand_p use_p;
2192   FOR_EACH_SSA_USE_OPERAND (use_p, def, iter, SSA_OP_USE)
2193     {
2194       tree use = USE_FROM_PTR (use_p);
2195       if (TREE_CODE (use) == SSA_NAME)
2196         {
2197           if (tree res = find_init_value (SSA_NAME_DEF_STMT (use)))
2198             return res;
2199         }
2200     }
2201
2202   return NULL_TREE;
2203 }
2204
2205 /* Return the init value, the value coming from outside the loop.  */
2206
2207 static tree
2208 find_init_value_close_phi (gphi *phi)
2209 {
2210   gcc_assert (gimple_phi_num_args (phi) == 1);
2211   tree use_arg = gimple_phi_arg_def (phi, 0);
2212   gimple *def = SSA_NAME_DEF_STMT (use_arg);
2213   return find_init_value (def);
2214 }
2215
2216
2217 tree translate_isl_ast_to_gimple::
2218 add_close_phis_to_outer_loops (tree last_merge_name, edge last_e,
2219                                gimple *old_close_phi)
2220 {
2221   sese_l &codegen_region = region->if_region->true_region->region;
2222   gimple *stmt = SSA_NAME_DEF_STMT (last_merge_name);
2223   basic_block bb = gimple_bb (stmt);
2224   if (!bb_in_sese_p (bb, codegen_region))
2225     return last_merge_name;
2226
2227   loop_p loop = bb->loop_father;
2228   if (!loop_in_sese_p (loop, codegen_region))
2229     return last_merge_name;
2230
2231   edge e = single_exit (loop);
2232
2233   if (dominated_by_p (CDI_DOMINATORS, e->dest, last_e->src))
2234     return last_merge_name;
2235
2236   tree old_name = gimple_phi_arg_def (old_close_phi, 0);
2237   tree old_close_phi_name = gimple_phi_result (old_close_phi);
2238
2239   bb = e->dest;
2240   if (!bb_contains_loop_close_phi_nodes (bb) || !single_succ_p (bb))
2241     bb = split_edge (e);
2242
2243   gphi *close_phi = create_phi_node (SSA_NAME_VAR (last_merge_name), bb);
2244   tree res = create_new_def_for (last_merge_name, close_phi,
2245                                  gimple_phi_result_ptr (close_phi));
2246   set_rename (old_close_phi_name, res);
2247   add_phi_arg (close_phi, last_merge_name, e, get_loc (old_name));
2248   last_merge_name = res;
2249
2250   return add_close_phis_to_outer_loops (last_merge_name, last_e, old_close_phi);
2251 }
2252
2253 /* Add phi nodes to all merge points of all the diamonds enclosing the loop of
2254    the close phi node PHI.  */
2255
2256 bool translate_isl_ast_to_gimple::
2257 add_close_phis_to_merge_points (gphi *old_close_phi, gphi *new_close_phi,
2258                                 tree default_value)
2259 {
2260   sese_l &codegen_region = region->if_region->true_region->region;
2261   basic_block default_value_bb = get_entry_bb (codegen_region);
2262   if (SSA_NAME == TREE_CODE (default_value))
2263     {
2264       gimple *stmt = SSA_NAME_DEF_STMT (default_value);
2265       if (!stmt || gimple_code (stmt) == GIMPLE_NOP)
2266         return false;
2267       default_value_bb = gimple_bb (stmt);
2268     }
2269
2270   basic_block new_close_phi_bb = gimple_bb (new_close_phi);
2271
2272   tree old_close_phi_name = gimple_phi_result (old_close_phi);
2273   tree new_close_phi_name = gimple_phi_result (new_close_phi);
2274   tree last_merge_name = new_close_phi_name;
2275   tree old_name = gimple_phi_arg_def (old_close_phi, 0);
2276
2277   int i;
2278   edge merge_e;
2279   FOR_EACH_VEC_ELT_REVERSE (merge_points, i, merge_e)
2280     {
2281       basic_block new_merge_bb = merge_e->src;
2282       if (!dominated_by_p (CDI_DOMINATORS, new_merge_bb, default_value_bb))
2283         continue;
2284
2285       last_merge_name = add_close_phis_to_outer_loops (last_merge_name, merge_e,
2286                                                        old_close_phi);
2287
2288       gphi *merge_phi = create_phi_node (SSA_NAME_VAR (old_close_phi_name), new_merge_bb);
2289       tree merge_res = create_new_def_for (old_close_phi_name, merge_phi,
2290                                            gimple_phi_result_ptr (merge_phi));
2291       set_rename (old_close_phi_name, merge_res);
2292
2293       edge from_loop = NULL, from_default_value = NULL;
2294       edge e;
2295       edge_iterator ei;
2296       FOR_EACH_EDGE (e, ei, new_merge_bb->preds)
2297         if (dominated_by_p (CDI_DOMINATORS, e->src, new_close_phi_bb))
2298           from_loop = e;
2299         else
2300           from_default_value = e;
2301
2302       /* Because CDI_POST_DOMINATORS are not updated, we only rely on
2303          CDI_DOMINATORS, which may not handle all cases where new_close_phi_bb
2304          is contained in another condition.  */
2305       if (!from_default_value || !from_loop)
2306         return false;
2307
2308       add_phi_arg (merge_phi, last_merge_name, from_loop, get_loc (old_name));
2309       add_phi_arg (merge_phi, default_value, from_default_value, get_loc (old_name));
2310
2311       if (dump_file)
2312         {
2313           fprintf (dump_file, "[codegen] Adding guard-phi: ");
2314           print_gimple_stmt (dump_file, merge_phi, 0, 0);
2315         }
2316
2317       update_stmt (merge_phi);
2318       last_merge_name = merge_res;
2319     }
2320
2321   return true;
2322 }
2323
2324 /* Copy all the loop-close phi args from BB to NEW_BB.  */
2325
2326 bool
2327 translate_isl_ast_to_gimple::copy_loop_close_phi_args (basic_block old_bb,
2328                                                        basic_block new_bb,
2329                                                        bool postpone)
2330 {
2331   for (gphi_iterator psi = gsi_start_phis (old_bb); !gsi_end_p (psi);
2332        gsi_next (&psi))
2333     {
2334       gphi *old_close_phi = psi.phi ();
2335       tree res = gimple_phi_result (old_close_phi);
2336       if (virtual_operand_p (res))
2337         continue;
2338
2339       if (is_gimple_reg (res) && scev_analyzable_p (res, region->region))
2340         /* Loop close phi nodes should not be scev_analyzable_p.  */
2341         gcc_unreachable ();
2342
2343       gphi *new_close_phi = create_phi_node (SSA_NAME_VAR (res), new_bb);
2344       tree new_res = create_new_def_for (res, new_close_phi,
2345                                          gimple_phi_result_ptr (new_close_phi));
2346       set_rename (res, new_res);
2347
2348       tree old_name = gimple_phi_arg_def (old_close_phi, 0);
2349       tree new_name = get_new_name (new_bb, old_name, old_bb, false);
2350
2351       /* Predecessor basic blocks of a loop close phi should have been code
2352          generated before.  FIXME: This is fixable by merging PHIs from inner
2353          loops as well.  See: gfortran.dg/graphite/interchange-3.f90.  */
2354       if (!new_name)
2355         return false;
2356
2357       add_phi_arg (new_close_phi, new_name, single_pred_edge (new_bb),
2358                    get_loc (old_name));
2359       if (dump_file)
2360         {
2361           fprintf (dump_file, "[codegen] Adding loop close phi: ");
2362           print_gimple_stmt (dump_file, new_close_phi, 0, 0);
2363         }
2364
2365       update_stmt (new_close_phi);
2366
2367       /* When there is no loop guard around this codegenerated loop, there is no
2368          need to collect the close-phi arg.  */
2369       if (merge_points.is_empty ())
2370         continue;
2371
2372       /* Add a PHI in the succ_new_bb for each close phi of the loop.  */
2373       tree default_value = find_init_value_close_phi (new_close_phi);
2374
2375       /* A close phi must come from a loop-phi having a default value.  */
2376       if (!default_value)
2377         {
2378           if (!postpone)
2379             return false;
2380
2381           region->incomplete_phis.safe_push (std::make_pair (old_close_phi,
2382                                                              new_close_phi));
2383           if (dump_file)
2384             {
2385               fprintf (dump_file, "[codegen] postpone close phi nodes: ");
2386               print_gimple_stmt (dump_file, new_close_phi, 0, 0);
2387             }
2388           continue;
2389         }
2390
2391       if (!add_close_phis_to_merge_points (old_close_phi, new_close_phi,
2392                                            default_value))
2393         return false;
2394     }
2395
2396   return true;
2397 }
2398
2399 /* Copy loop close phi nodes from BB to NEW_BB.  */
2400
2401 bool
2402 translate_isl_ast_to_gimple::copy_loop_close_phi_nodes (basic_block old_bb,
2403                                                         basic_block new_bb)
2404 {
2405   if (dump_file)
2406     fprintf (dump_file, "[codegen] copying loop close phi nodes in bb_%d.\n",
2407              new_bb->index);
2408   /* Loop close phi nodes should have only one argument.  */
2409   gcc_assert (1 == EDGE_COUNT (old_bb->preds));
2410
2411   return copy_loop_close_phi_args (old_bb, new_bb, true);
2412 }
2413
2414
2415 /* Add NEW_NAME as the ARGNUM-th arg of NEW_PHI which is in NEW_BB.
2416    DOMINATING_PRED is the predecessor basic block of OLD_BB which dominates the
2417    other pred of OLD_BB as well.  If no such basic block exists then it is NULL.
2418    NON_DOMINATING_PRED is a pred which does not dominate OLD_BB, it cannot be
2419    NULL.
2420
2421    Case1: OLD_BB->preds {BB1, BB2} and BB1 does not dominate BB2 and vice versa.
2422    In this case DOMINATING_PRED = NULL.
2423
2424    Case2: OLD_BB->preds {BB1, BB2} and BB1 dominates BB2.
2425
2426    Returns true on successful copy of the args, false otherwise.  */
2427
2428 bool
2429 translate_isl_ast_to_gimple::
2430 add_phi_arg_for_new_expr (tree old_phi_args[2], tree new_phi_args[2],
2431                           edge old_bb_dominating_edge,
2432                           edge old_bb_non_dominating_edge,
2433                           gphi *phi, gphi *new_phi,
2434                           basic_block new_bb)
2435 {
2436   basic_block def_pred[2] = { NULL, NULL };
2437   int not_found_bb_index = -1;
2438   for (int i = 0; i < 2; i++)
2439     {
2440       /* If the corresponding def_bb could not be found the entry will be
2441          NULL.  */
2442       if (TREE_CODE (old_phi_args[i]) == INTEGER_CST)
2443         def_pred[i] = get_def_bb_for_const (new_bb,
2444                                             gimple_phi_arg_edge (phi, i)->src);
2445       else if (new_phi_args[i] && (TREE_CODE (new_phi_args[i]) == SSA_NAME))
2446         def_pred[i] = gimple_bb (SSA_NAME_DEF_STMT (new_phi_args[i]));
2447
2448       if (!def_pred[i])
2449         {
2450           /* When non are available bail out.  */
2451           if (not_found_bb_index != -1)
2452             return false;
2453           not_found_bb_index = i;
2454         }
2455     }
2456
2457   /* Here we are pattern matching on the structure of CFG w.r.t. old one.  */
2458   if (old_bb_dominating_edge)
2459     {
2460       if (not_found_bb_index != -1)
2461         return false;
2462
2463       basic_block new_pred1 = (*new_bb->preds)[0]->src;
2464       basic_block new_pred2 = (*new_bb->preds)[1]->src;
2465       vec <basic_block> *bbs
2466         = region->copied_bb_map->get (old_bb_non_dominating_edge->src);
2467
2468       /* Could not find a mapping.  */
2469       if (!bbs)
2470         return false;
2471
2472       basic_block new_pred = NULL;
2473       basic_block b;
2474       int i;
2475       FOR_EACH_VEC_ELT (*bbs, i, b)
2476         {
2477           if (dominated_by_p (CDI_DOMINATORS, new_pred1, b))
2478             {
2479               /* FIXME: If we have already found new_pred then we have to
2480                  disambiguate, bail out for now.  */
2481               if (new_pred)
2482                 return false;
2483               new_pred = new_pred1;
2484             }
2485           if (dominated_by_p (CDI_DOMINATORS, new_pred2, b))
2486             {
2487               /* FIXME: If we have already found new_pred then we have to either
2488                  it dominates both or we have to disambiguate, bail out.  */
2489               if (new_pred)
2490                 return false;
2491               new_pred = new_pred2;
2492             }
2493         }
2494
2495       if (!new_pred)
2496         return false;
2497
2498       edge new_non_dominating_edge = find_edge (new_pred, new_bb);
2499       gcc_assert (new_non_dominating_edge);
2500       /* FIXME: Validate each args just like in loop-phis.  */
2501       /* By the process of elimination we first insert insert phi-edge for
2502          non-dominating pred which is computed above and then we insert the
2503          remaining one.  */
2504       int inserted_edge = 0;
2505       for (; inserted_edge < 2; inserted_edge++)
2506         {
2507           edge new_bb_pred_edge = gimple_phi_arg_edge (new_phi, inserted_edge);
2508           if (new_non_dominating_edge == new_bb_pred_edge)
2509             {
2510               add_phi_arg (new_phi, new_phi_args[inserted_edge],
2511                            new_non_dominating_edge,
2512                            get_loc (old_phi_args[inserted_edge]));
2513               break;
2514             }
2515         }
2516       if (inserted_edge == 2)
2517         return false;
2518
2519       int edge_dominating = inserted_edge == 0 ? 1 : 0;
2520
2521       edge new_dominating_edge = NULL;
2522       for (inserted_edge = 0; inserted_edge < 2; inserted_edge++)
2523         {
2524           edge e = gimple_phi_arg_edge (new_phi, inserted_edge);
2525           if (e != new_non_dominating_edge)
2526             {
2527               new_dominating_edge = e;
2528               add_phi_arg (new_phi, new_phi_args[edge_dominating],
2529                            new_dominating_edge,
2530                            get_loc (old_phi_args[inserted_edge]));
2531               break;
2532             }
2533         }
2534       gcc_assert (new_dominating_edge);
2535     }
2536   else
2537     {
2538       /* Classic diamond structure: both edges are non-dominating.  We need to
2539          find one unique edge then the other can be found be elimination.  If
2540          any definition (def_pred) dominates both the preds of new_bb then we
2541          bail out.  Entries of def_pred maybe NULL, in that case we must
2542          uniquely find pred with help of only one entry.  */
2543       edge new_e[2] = { NULL, NULL };
2544       for (int i = 0; i < 2; i++)
2545         {
2546           edge e;
2547           edge_iterator ei;
2548           FOR_EACH_EDGE (e, ei, new_bb->preds)
2549             if (def_pred[i]
2550                 && dominated_by_p (CDI_DOMINATORS, e->src, def_pred[i]))
2551               {
2552                 if (new_e[i])
2553                   /* We do not know how to handle the case when def_pred
2554                      dominates more than a predecessor.  */
2555                   return false;
2556                 new_e[i] = e;
2557               }
2558         }
2559
2560       gcc_assert (new_e[0] || new_e[1]);
2561
2562       /* Find the other edge by process of elimination.  */
2563       if (not_found_bb_index != -1)
2564         {
2565           gcc_assert (!new_e[not_found_bb_index]);
2566           int found_bb_index = not_found_bb_index == 1 ? 0 : 1;
2567           edge e;
2568           edge_iterator ei;
2569           FOR_EACH_EDGE (e, ei, new_bb->preds)
2570             {
2571               if (new_e[found_bb_index] == e)
2572                 continue;
2573               new_e[not_found_bb_index] = e;
2574             }
2575         }
2576
2577       /* Add edges to phi args.  */
2578       for (int i = 0; i < 2; i++)
2579         add_phi_arg (new_phi, new_phi_args[i], new_e[i],
2580                      get_loc (old_phi_args[i]));
2581     }
2582
2583   return true;
2584 }
2585
2586 /* Copy the arguments of cond-phi node PHI, to NEW_PHI in the codegenerated
2587    region.  If postpone is true and it isn't possible to copy any arg of PHI,
2588    the PHI is added to the REGION->INCOMPLETE_PHIS to be codegenerated later.
2589    Returns false if the copying was unsuccessful.  */
2590
2591 bool
2592 translate_isl_ast_to_gimple::copy_cond_phi_args (gphi *phi, gphi *new_phi,
2593                                                  vec<tree> iv_map,
2594                                                  bool postpone)
2595 {
2596   if (dump_file)
2597     fprintf (dump_file, "[codegen] copying cond phi args.\n");
2598   gcc_assert (2 == gimple_phi_num_args (phi));
2599
2600   basic_block new_bb = gimple_bb (new_phi);
2601   loop_p loop = gimple_bb (phi)->loop_father;
2602
2603   basic_block old_bb = gimple_bb (phi);
2604   edge old_bb_non_dominating_edge = NULL, old_bb_dominating_edge = NULL;
2605
2606   edge e;
2607   edge_iterator ei;
2608   FOR_EACH_EDGE (e, ei, old_bb->preds)
2609     if (!dominated_by_p (CDI_DOMINATORS, old_bb, e->src))
2610       old_bb_non_dominating_edge = e;
2611     else
2612       old_bb_dominating_edge = e;
2613
2614   gcc_assert (!dominated_by_p (CDI_DOMINATORS, old_bb,
2615                                old_bb_non_dominating_edge->src));
2616
2617   tree new_phi_args[2];
2618   tree old_phi_args[2];
2619
2620   for (unsigned i = 0; i < gimple_phi_num_args (phi); i++)
2621     {
2622       tree old_name = gimple_phi_arg_def (phi, i);
2623       tree new_name = get_new_name (new_bb, old_name, old_bb, false);
2624       old_phi_args[i] = old_name;
2625       if (new_name)
2626         {
2627           new_phi_args [i] = new_name;
2628           continue;
2629         }
2630
2631       /* If the phi-arg was a parameter.  */
2632       if (vec_find (region->params, old_name) != -1)
2633         {
2634           new_phi_args [i] = old_name;
2635           if (dump_file)
2636             {
2637               fprintf (dump_file,
2638                        "[codegen] parameter argument to phi, new_expr: ");
2639               print_generic_expr (dump_file, new_phi_args[i], 0);
2640               fprintf (dump_file, "\n");
2641             }
2642           continue;
2643         }
2644
2645       gimple *old_def_stmt = SSA_NAME_DEF_STMT (old_name);
2646       if (!old_def_stmt || gimple_code (old_def_stmt) == GIMPLE_NOP)
2647         /* FIXME: If the phi arg was a function arg, or wasn't defined, just use
2648            the old name.  */
2649         return false;
2650
2651       if (postpone)
2652         {
2653           /* If the phi-arg is scev-analyzeable but only in the first stage.  */
2654           if (is_gimple_reg (old_name)
2655               && scev_analyzable_p (old_name, region->region))
2656             {
2657               gimple_seq stmts;
2658               tree new_expr = get_rename_from_scev (old_name, &stmts, loop,
2659                                                     new_bb, old_bb, iv_map);
2660               if (codegen_error_p ())
2661                 return false;
2662
2663               gcc_assert (new_expr);
2664               if (dump_file)
2665                 {
2666                   fprintf (dump_file,
2667                            "[codegen] scev analyzeable, new_expr: ");
2668                   print_generic_expr (dump_file, new_expr, 0);
2669                   fprintf (dump_file, "\n");
2670                 }
2671               gsi_insert_earliest (stmts);
2672               new_phi_args [i] = new_name;
2673               continue;
2674             }
2675
2676           /* Postpone code gen for later for back-edges.  */
2677           region->incomplete_phis.safe_push (std::make_pair (phi, new_phi));
2678
2679           if (dump_file)
2680             {
2681               fprintf (dump_file, "[codegen] postpone cond phi nodes: ");
2682               print_gimple_stmt (dump_file, new_phi, 0, 0);
2683             }
2684
2685           new_phi_args [i] = NULL_TREE;
2686           continue;
2687         }
2688       else
2689         /* Either we should add the arg to phi or, we should postpone.  */
2690         return false;
2691     }
2692
2693   /* If none of the args have been determined in the first stage then wait until
2694      later.  */
2695   if (postpone && !new_phi_args[0] && !new_phi_args[1])
2696     return true;
2697
2698   return add_phi_arg_for_new_expr (old_phi_args, new_phi_args,
2699                                    old_bb_dominating_edge,
2700                                    old_bb_non_dominating_edge,
2701                                    phi, new_phi, new_bb);
2702 }
2703
2704 /* Copy cond phi nodes from BB to NEW_BB.  A cond-phi node is a basic block
2705    containing phi nodes coming from two predecessors, and none of them are back
2706    edges.  */
2707
2708 bool
2709 translate_isl_ast_to_gimple::copy_cond_phi_nodes (basic_block bb,
2710                                                   basic_block new_bb,
2711                                                   vec<tree> iv_map)
2712 {
2713
2714   gcc_assert (!bb_contains_loop_close_phi_nodes (bb));
2715
2716   if (dump_file)
2717     fprintf (dump_file, "[codegen] copying cond phi nodes in bb_%d.\n",
2718              new_bb->index);
2719
2720   /* Cond phi nodes should have exactly two arguments.  */
2721   gcc_assert (2 == EDGE_COUNT (bb->preds));
2722
2723   for (gphi_iterator psi = gsi_start_phis (bb); !gsi_end_p (psi);
2724        gsi_next (&psi))
2725     {
2726       gphi *phi = psi.phi ();
2727       tree res = gimple_phi_result (phi);
2728       if (virtual_operand_p (res))
2729         continue;
2730       if (is_gimple_reg (res) && scev_analyzable_p (res, region->region))
2731         /* Cond phi nodes should not be scev_analyzable_p.  */
2732         gcc_unreachable ();
2733
2734       gphi *new_phi = create_phi_node (SSA_NAME_VAR (res), new_bb);
2735       tree new_res = create_new_def_for (res, new_phi,
2736                                          gimple_phi_result_ptr (new_phi));
2737       set_rename (res, new_res);
2738
2739       if (!copy_cond_phi_args (phi, new_phi, iv_map, true))
2740         return false;
2741
2742       update_stmt (new_phi);
2743     }
2744
2745   return true;
2746 }
2747
2748 /* Return true if STMT should be copied from region to the new code-generated
2749    region.  LABELs, CONDITIONS, induction-variables and region parameters need
2750    not be copied.  */
2751
2752 static bool
2753 should_copy_to_new_region (gimple *stmt, sese_info_p region)
2754 {
2755   /* Do not copy labels or conditions.  */
2756   if (gimple_code (stmt) == GIMPLE_LABEL
2757       || gimple_code (stmt) == GIMPLE_COND)
2758     return false;
2759
2760   tree lhs;
2761   /* Do not copy induction variables.  */
2762   if (is_gimple_assign (stmt)
2763       && (lhs = gimple_assign_lhs (stmt))
2764       && TREE_CODE (lhs) == SSA_NAME
2765       && is_gimple_reg (lhs)
2766       && scev_analyzable_p (lhs, region->region))
2767     return false;
2768
2769   /* Do not copy parameters that have been generated in the header of the
2770      scop.  */
2771   if (is_gimple_assign (stmt)
2772       && (lhs = gimple_assign_lhs (stmt))
2773       && TREE_CODE (lhs) == SSA_NAME
2774       && region->parameter_rename_map->get(lhs))
2775     return false;
2776
2777   return true;
2778 }
2779
2780 /* Create new names for all the definitions created by COPY and add replacement
2781    mappings for each new name.  */
2782
2783 void
2784 translate_isl_ast_to_gimple::set_rename_for_each_def (gimple *stmt)
2785 {
2786   def_operand_p def_p;
2787   ssa_op_iter op_iter;
2788   FOR_EACH_SSA_DEF_OPERAND (def_p, stmt, op_iter, SSA_OP_ALL_DEFS)
2789     {
2790       tree old_name = DEF_FROM_PTR (def_p);
2791       tree new_name = create_new_def_for (old_name, stmt, def_p);
2792       set_rename (old_name, new_name);
2793     }
2794 }
2795
2796 /* Duplicates the statements of basic block BB into basic block NEW_BB
2797    and compute the new induction variables according to the IV_MAP.
2798    CODEGEN_ERROR is set when the code generation cannot continue.  */
2799
2800 bool
2801 translate_isl_ast_to_gimple::graphite_copy_stmts_from_block (basic_block bb,
2802                                                              basic_block new_bb,
2803                                                              vec<tree> iv_map)
2804 {
2805   /* Iterator poining to the place where new statement (s) will be inserted.  */
2806   gimple_stmt_iterator gsi_tgt = gsi_last_bb (new_bb);
2807
2808   for (gimple_stmt_iterator gsi = gsi_start_bb (bb); !gsi_end_p (gsi);
2809        gsi_next (&gsi))
2810     {
2811       gimple *stmt = gsi_stmt (gsi);
2812       if (!should_copy_to_new_region (stmt, region))
2813         continue;
2814
2815       /* Create a new copy of STMT and duplicate STMT's virtual
2816          operands.  */
2817       gimple *copy = gimple_copy (stmt);
2818       gsi_insert_after (&gsi_tgt, copy, GSI_NEW_STMT);
2819
2820       if (dump_file)
2821         {
2822           fprintf (dump_file, "[codegen] inserting statement: ");
2823           print_gimple_stmt (dump_file, copy, 0, 0);
2824         }
2825
2826       maybe_duplicate_eh_stmt (copy, stmt);
2827       gimple_duplicate_stmt_histograms (cfun, copy, cfun, stmt);
2828
2829       /* Crete new names for each def in the copied stmt.  */
2830       set_rename_for_each_def (copy);
2831
2832       loop_p loop = bb->loop_father;
2833       if (rename_uses (copy, &gsi_tgt, bb, loop, iv_map))
2834         {
2835           fold_stmt_inplace (&gsi_tgt);
2836           gcc_assert (gsi_stmt (gsi_tgt) == copy);
2837         }
2838
2839       if (codegen_error_p ())
2840         return false;
2841
2842       /* For each SSA_NAME in the parameter_rename_map rename their usage.  */
2843       ssa_op_iter iter;
2844       use_operand_p use_p;
2845       if (!is_gimple_debug (copy))
2846         FOR_EACH_SSA_USE_OPERAND (use_p, copy, iter, SSA_OP_USE)
2847           {
2848             tree old_name = USE_FROM_PTR (use_p);
2849
2850             if (TREE_CODE (old_name) != SSA_NAME
2851                 || SSA_NAME_IS_DEFAULT_DEF (old_name))
2852               continue;
2853
2854             tree *new_expr = region->parameter_rename_map->get (old_name);
2855             if (!new_expr)
2856               continue;
2857
2858             replace_exp (use_p, *new_expr);
2859           }
2860
2861       update_stmt (copy);
2862     }
2863
2864   return true;
2865 }
2866
2867
2868 /* Given a basic block containing close-phi it returns the new basic block where
2869    to insert a copy of the close-phi nodes.  All the uses in close phis should
2870    come from a single loop otherwise it returns NULL.  */
2871
2872 edge
2873 translate_isl_ast_to_gimple::edge_for_new_close_phis (basic_block bb)
2874 {
2875   /* Make sure that NEW_BB is the new_loop->exit->dest.  We find the definition
2876      of close phi in the original code and then find the mapping of basic block
2877      defining that variable.  If there are multiple close-phis and they are
2878      defined in different loops (in the original or in the new code) because of
2879      loop splitting, then we bail out.  */
2880   loop_p new_loop = NULL;
2881   for (gphi_iterator psi = gsi_start_phis (bb); !gsi_end_p (psi);
2882        gsi_next (&psi))
2883     {
2884       gphi *phi = psi.phi ();
2885       tree name = gimple_phi_arg_def (phi, 0);
2886       basic_block old_loop_bb = gimple_bb (SSA_NAME_DEF_STMT (name));
2887
2888       vec <basic_block> *bbs = region->copied_bb_map->get (old_loop_bb);
2889       if (!bbs || bbs->length () != 1)
2890         /* This is one of the places which shows preserving original structure
2891            is not always possible, as we may need to insert close PHI for a loop
2892            where the latch does not have any mapping, or the mapping is
2893            ambiguous.  */
2894         return NULL;
2895
2896       if (!new_loop)
2897         new_loop = (*bbs)[0]->loop_father;
2898       else if (new_loop != (*bbs)[0]->loop_father)
2899         return NULL;
2900     }
2901
2902   if (!new_loop)
2903     return NULL;
2904
2905   return single_exit (new_loop);
2906 }
2907
2908 /* Copies BB and includes in the copied BB all the statements that can
2909    be reached following the use-def chains from the memory accesses,
2910    and returns the next edge following this new block.  codegen_error is
2911    set when the code generation cannot continue.  */
2912
2913 edge
2914 translate_isl_ast_to_gimple::copy_bb_and_scalar_dependences (basic_block bb,
2915                                                              edge next_e,
2916                                                              vec<tree> iv_map)
2917 {
2918   int num_phis = number_of_phi_nodes (bb);
2919
2920   if (region->copied_bb_map->get (bb))
2921     {
2922       /* FIXME: we should be able to handle phi nodes with args coming from
2923          outside the region.  */
2924       if (num_phis)
2925         {
2926           codegen_error = true;
2927           return NULL;
2928         }
2929     }
2930
2931   basic_block new_bb = NULL;
2932   if (bb_contains_loop_close_phi_nodes (bb))
2933     {
2934       if (dump_file)
2935         fprintf (dump_file, "[codegen] bb_%d contains close phi nodes.\n",
2936                  bb->index);
2937
2938       edge e = edge_for_new_close_phis (bb);
2939       if (!e)
2940         {
2941           codegen_error = true;
2942           return NULL;
2943         }
2944
2945       basic_block phi_bb = e->dest;
2946
2947       if (!bb_contains_loop_close_phi_nodes (phi_bb) || !single_succ_p (phi_bb))
2948         phi_bb = split_edge (e);
2949
2950       gcc_assert (single_pred_edge (phi_bb)->src->loop_father
2951                   != single_pred_edge (phi_bb)->dest->loop_father);
2952
2953       if (!copy_loop_close_phi_nodes (bb, phi_bb))
2954         {
2955           codegen_error = true;
2956           return NULL;
2957         }
2958
2959       if (e == next_e)
2960         new_bb = phi_bb;
2961       else
2962         new_bb = split_edge (next_e);
2963     }
2964   else
2965     {
2966       new_bb = split_edge (next_e);
2967       if (num_phis > 0 && bb_contains_loop_phi_nodes (bb))
2968         {
2969           basic_block phi_bb = next_e->dest->loop_father->header;
2970
2971           /* At this point we are unable to codegenerate by still preserving the SSA
2972              structure because maybe the loop is completely unrolled and the PHIs
2973              and cross-bb scalar dependencies are untrackable w.r.t. the original
2974              code.  See gfortran.dg/graphite/pr29832.f90.  */
2975           if (EDGE_COUNT (bb->preds) != EDGE_COUNT (phi_bb->preds))
2976             {
2977               codegen_error = true;
2978               return NULL;
2979             }
2980
2981           /* In case isl did some loop peeling, like this:
2982
2983                S_8(0);
2984                for (int c1 = 1; c1 <= 5; c1 += 1) {
2985                  S_8(c1);
2986                }
2987                S_8(6);
2988
2989              there should be no loop-phi nodes in S_8(0).
2990
2991              FIXME: We need to reason about dynamic instances of S_8, i.e., the
2992              values of all scalar variables: for the moment we instantiate only
2993              SCEV analyzable expressions on the iteration domain, and we need to
2994              extend that to reductions that cannot be analyzed by SCEV.  */
2995           if (!bb_in_sese_p (phi_bb, region->if_region->true_region->region))
2996             {
2997               codegen_error = true;
2998               return NULL;
2999             }
3000
3001           if (dump_file)
3002             fprintf (dump_file, "[codegen] bb_%d contains loop phi nodes.\n",
3003                      bb->index);
3004           if (!copy_loop_phi_nodes (bb, phi_bb))
3005             {
3006               codegen_error = true;
3007               return NULL;
3008             }
3009         }
3010       else if (num_phis > 0)
3011         {
3012           if (dump_file)
3013             fprintf (dump_file, "[codegen] bb_%d contains cond phi nodes.\n",
3014                      bb->index);
3015
3016           basic_block phi_bb = single_pred (new_bb);
3017           loop_p loop_father = new_bb->loop_father;
3018
3019           /* Move back until we find the block with two predecessors.  */
3020           while (single_pred_p (phi_bb))
3021             phi_bb = single_pred_edge (phi_bb)->src;
3022
3023           /* If a corresponding merge-point was not found, then abort codegen.  */
3024           if (phi_bb->loop_father != loop_father
3025               || !bb_in_sese_p (phi_bb, region->if_region->true_region->region)
3026               || !copy_cond_phi_nodes (bb, phi_bb, iv_map))
3027             {
3028               codegen_error = true;
3029               return NULL;
3030             }
3031         }
3032     }
3033
3034   if (dump_file)
3035     fprintf (dump_file, "[codegen] copying from bb_%d to bb_%d.\n",
3036              bb->index, new_bb->index);
3037
3038   vec <basic_block> *copied_bbs = region->copied_bb_map->get (bb);
3039   if (copied_bbs)
3040     copied_bbs->safe_push (new_bb);
3041   else
3042     {
3043       vec<basic_block> bbs;
3044       bbs.create (2);
3045       bbs.safe_push (new_bb);
3046       region->copied_bb_map->put (bb, bbs);
3047     }
3048
3049   if (!graphite_copy_stmts_from_block (bb, new_bb, iv_map))
3050     {
3051       codegen_error = true;
3052       return NULL;
3053     }
3054
3055   return single_succ_edge (new_bb);
3056 }
3057
3058 /* Patch the missing arguments of the phi nodes.  */
3059
3060 void
3061 translate_isl_ast_to_gimple::translate_pending_phi_nodes ()
3062 {
3063   int i;
3064   phi_rename *rename;
3065   FOR_EACH_VEC_ELT (region->incomplete_phis, i, rename)
3066     {
3067       gphi *old_phi = rename->first;
3068       gphi *new_phi = rename->second;
3069       basic_block old_bb = gimple_bb (old_phi);
3070       basic_block new_bb = gimple_bb (new_phi);
3071
3072       /* First edge is the init edge and second is the back edge.  */
3073       init_back_edge_pair_t ibp_old_bb = get_edges (old_bb);
3074       init_back_edge_pair_t ibp_new_bb = get_edges (new_bb);
3075
3076       if (dump_file)
3077         {
3078           fprintf (dump_file, "[codegen] translating pending old-phi: ");
3079           print_gimple_stmt (dump_file, old_phi, 0, 0);
3080         }
3081
3082       auto_vec <tree, 1> iv_map;
3083       if (bb_contains_loop_phi_nodes (new_bb))
3084         codegen_error = !copy_loop_phi_args (old_phi, ibp_old_bb, new_phi,
3085                                             ibp_new_bb, false);
3086       else if (bb_contains_loop_close_phi_nodes (new_bb))
3087         codegen_error = !copy_loop_close_phi_args (old_bb, new_bb, false);
3088       else
3089         codegen_error = !copy_cond_phi_args (old_phi, new_phi, iv_map, false);
3090
3091       if (dump_file)
3092         {
3093           fprintf (dump_file, "[codegen] to new-phi: ");
3094           print_gimple_stmt (dump_file, new_phi, 0, 0);
3095         }
3096       if (codegen_error)
3097         return;
3098     }
3099 }
3100
3101 /* Prints NODE to FILE.  */
3102
3103 void
3104 translate_isl_ast_to_gimple::print_isl_ast_node (FILE *file,
3105                                                  __isl_keep isl_ast_node *node,
3106                                                  __isl_keep isl_ctx *ctx) const
3107 {
3108   isl_printer *prn = isl_printer_to_file (ctx, file);
3109   prn = isl_printer_set_output_format (prn, ISL_FORMAT_C);
3110   prn = isl_printer_print_ast_node (prn, node);
3111   prn = isl_printer_print_str (prn, "\n");
3112   isl_printer_free (prn);
3113 }
3114
3115 /* Add isl's parameter identifiers and corresponding trees to ivs_params.  */
3116
3117 void
3118 translate_isl_ast_to_gimple::add_parameters_to_ivs_params (scop_p scop,
3119                                                            ivs_params &ip)
3120 {
3121   sese_info_p region = scop->scop_info;
3122   unsigned nb_parameters = isl_set_dim (scop->param_context, isl_dim_param);
3123   gcc_assert (nb_parameters == region->params.length ());
3124   unsigned i;
3125   for (i = 0; i < nb_parameters; i++)
3126     {
3127       isl_id *tmp_id = isl_set_get_dim_id (scop->param_context,
3128                                            isl_dim_param, i);
3129       ip[tmp_id] = region->params[i];
3130     }
3131 }
3132
3133
3134 /* Generates a build, which specifies the constraints on the parameters.  */
3135
3136 __isl_give isl_ast_build *
3137 translate_isl_ast_to_gimple::generate_isl_context (scop_p scop)
3138 {
3139   isl_set *context_isl = isl_set_params (isl_set_copy (scop->param_context));
3140   return isl_ast_build_from_context (context_isl);
3141 }
3142
3143 /* Get the maximal number of schedule dimensions in the scop SCOP.  */
3144
3145 int
3146 translate_isl_ast_to_gimple::get_max_schedule_dimensions (scop_p scop)
3147 {
3148   int i;
3149   poly_bb_p pbb;
3150   int schedule_dims = 0;
3151
3152   FOR_EACH_VEC_ELT (scop->pbbs, i, pbb)
3153     {
3154       int pbb_schedule_dims = isl_map_dim (pbb->transformed, isl_dim_out);
3155       if (pbb_schedule_dims > schedule_dims)
3156         schedule_dims = pbb_schedule_dims;
3157     }
3158
3159   return schedule_dims;
3160 }
3161
3162 /* Extend the schedule to NB_SCHEDULE_DIMS schedule dimensions.
3163
3164    For schedules with different dimensionality, the isl AST generator can not
3165    define an order and will just randomly choose an order.  The solution to this
3166    problem is to extend all schedules to the maximal number of schedule
3167    dimensions (using '0's for the remaining values).  */
3168
3169 __isl_give isl_map *
3170 translate_isl_ast_to_gimple::extend_schedule (__isl_take isl_map *schedule,
3171                                               int nb_schedule_dims)
3172 {
3173   int tmp_dims = isl_map_dim (schedule, isl_dim_out);
3174   schedule =
3175     isl_map_add_dims (schedule, isl_dim_out, nb_schedule_dims - tmp_dims);
3176   isl_val *zero =
3177     isl_val_int_from_si (isl_map_get_ctx (schedule), 0);
3178   int i;
3179   for (i = tmp_dims; i < nb_schedule_dims; i++)
3180     {
3181       schedule
3182         = isl_map_fix_val (schedule, isl_dim_out, i, isl_val_copy (zero));
3183     }
3184   isl_val_free (zero);
3185   return schedule;
3186 }
3187
3188 /* Generates a schedule, which specifies an order used to
3189    visit elements in a domain.  */
3190
3191 __isl_give isl_union_map *
3192 translate_isl_ast_to_gimple::generate_isl_schedule (scop_p scop)
3193 {
3194   int nb_schedule_dims = get_max_schedule_dimensions (scop);
3195   int i;
3196   poly_bb_p pbb;
3197   isl_union_map *schedule_isl =
3198     isl_union_map_empty (isl_set_get_space (scop->param_context));
3199
3200   FOR_EACH_VEC_ELT (scop->pbbs, i, pbb)
3201     {
3202       /* Dead code elimination: when the domain of a PBB is empty,
3203          don't generate code for the PBB.  */
3204       if (isl_set_is_empty (pbb->domain))
3205         continue;
3206
3207       isl_map *bb_schedule = isl_map_copy (pbb->transformed);
3208       bb_schedule = isl_map_intersect_domain (bb_schedule,
3209                                               isl_set_copy (pbb->domain));
3210       bb_schedule = extend_schedule (bb_schedule, nb_schedule_dims);
3211       bb_schedule = isl_map_coalesce (bb_schedule);
3212       schedule_isl
3213         = isl_union_map_union (schedule_isl,
3214                                isl_union_map_from_map (bb_schedule));
3215       schedule_isl = isl_union_map_coalesce (schedule_isl);
3216     }
3217   return schedule_isl;
3218 }
3219
3220 /* This method is executed before the construction of a for node.  */
3221 __isl_give isl_id *
3222 ast_build_before_for (__isl_keep isl_ast_build *build, void *user)
3223 {
3224   isl_union_map *dependences = (isl_union_map *) user;
3225   ast_build_info *for_info = XNEW (struct ast_build_info);
3226   isl_union_map *schedule = isl_ast_build_get_schedule (build);
3227   isl_space *schedule_space = isl_ast_build_get_schedule_space (build);
3228   int dimension = isl_space_dim (schedule_space, isl_dim_out);
3229   for_info->is_parallelizable =
3230     !carries_deps (schedule, dependences, dimension);
3231   isl_union_map_free (schedule);
3232   isl_space_free (schedule_space);
3233   isl_id *id = isl_id_alloc (isl_ast_build_get_ctx (build), "", for_info);
3234   return id;
3235 }
3236
3237 #ifdef HAVE_ISL_OPTIONS_SET_SCHEDULE_SERIALIZE_SCCS
3238 /* Set the separate option for all schedules.  This helps reducing control
3239    overhead.  */
3240
3241 __isl_give isl_schedule *
3242 translate_isl_ast_to_gimple::set_options_for_schedule_tree
3243 (__isl_take isl_schedule *schedule)
3244 {
3245   return isl_schedule_map_schedule_node_bottom_up
3246     (schedule, set_separate_option, NULL);
3247 }
3248 #endif
3249
3250 /* Set the separate option for all dimensions.
3251    This helps to reduce control overhead.  */
3252
3253 __isl_give isl_ast_build *
3254 translate_isl_ast_to_gimple::set_options (__isl_take isl_ast_build *control,
3255                                           __isl_keep isl_union_map *schedule)
3256 {
3257   isl_ctx *ctx = isl_union_map_get_ctx (schedule);
3258   isl_space *range_space = isl_space_set_alloc (ctx, 0, 1);
3259   range_space =
3260     isl_space_set_tuple_name (range_space, isl_dim_set, "separate");
3261   isl_union_set *range =
3262     isl_union_set_from_set (isl_set_universe (range_space));
3263   isl_union_set *domain = isl_union_map_range (isl_union_map_copy (schedule));
3264   domain = isl_union_set_universe (domain);
3265   isl_union_map *options = isl_union_map_from_domain_and_range (domain, range);
3266   return isl_ast_build_set_options (control, options);
3267 }
3268
3269 /* Generate isl AST from schedule of SCOP.  Also, collects IVS_PARAMS in IP.  */
3270
3271 __isl_give isl_ast_node *
3272 translate_isl_ast_to_gimple::scop_to_isl_ast (scop_p scop, ivs_params &ip)
3273 {
3274   isl_ast_node *ast_isl = NULL;
3275   /* Generate loop upper bounds that consist of the current loop iterator, an
3276      operator (< or <=) and an expression not involving the iterator.  If this
3277      option is not set, then the current loop iterator may appear several times
3278      in the upper bound.  See the isl manual for more details.  */
3279   isl_options_set_ast_build_atomic_upper_bound (scop->isl_context, true);
3280
3281   add_parameters_to_ivs_params (scop, ip);
3282   isl_union_map *schedule_isl = generate_isl_schedule (scop);
3283   isl_ast_build *context_isl = generate_isl_context (scop);
3284   context_isl = set_options (context_isl, schedule_isl);
3285   if (flag_loop_parallelize_all)
3286     {
3287       isl_union_map *dependence = scop_get_dependences (scop);
3288       context_isl =
3289         isl_ast_build_set_before_each_for (context_isl, ast_build_before_for,
3290                                            dependence);
3291     }
3292
3293 #ifdef HAVE_ISL_OPTIONS_SET_SCHEDULE_SERIALIZE_SCCS
3294   if (scop->schedule)
3295     {
3296       scop->schedule = set_options_for_schedule_tree (scop->schedule);
3297       ast_isl = isl_ast_build_node_from_schedule (context_isl, scop->schedule);
3298       isl_union_map_free(schedule_isl);
3299     }
3300   else
3301     ast_isl = isl_ast_build_ast_from_schedule (context_isl, schedule_isl);
3302 #else
3303   ast_isl = isl_ast_build_ast_from_schedule (context_isl, schedule_isl);
3304   isl_schedule_free (scop->schedule);
3305 #endif
3306
3307   isl_ast_build_free (context_isl);
3308   return ast_isl;
3309 }
3310
3311 /* Copy def from sese REGION to the newly created TO_REGION. TR is defined by
3312    DEF_STMT. GSI points to entry basic block of the TO_REGION.  */
3313
3314 static void
3315 copy_def (tree tr, gimple *def_stmt, sese_info_p region, sese_info_p to_region,
3316           gimple_stmt_iterator *gsi)
3317 {
3318   if (!defined_in_sese_p (tr, region->region))
3319     return;
3320
3321   ssa_op_iter iter;
3322   use_operand_p use_p;
3323   FOR_EACH_SSA_USE_OPERAND (use_p, def_stmt, iter, SSA_OP_USE)
3324     {
3325       tree use_tr = USE_FROM_PTR (use_p);
3326
3327       /* Do not copy parameters that have been generated in the header of the
3328          scop.  */
3329       if (region->parameter_rename_map->get(use_tr))
3330         continue;
3331
3332       gimple *def_of_use = SSA_NAME_DEF_STMT (use_tr);
3333       if (!def_of_use)
3334         continue;
3335
3336       copy_def (use_tr, def_of_use, region, to_region, gsi);
3337     }
3338
3339   gimple *copy = gimple_copy (def_stmt);
3340   gsi_insert_after (gsi, copy, GSI_NEW_STMT);
3341
3342   /* Create new names for all the definitions created by COPY and
3343      add replacement mappings for each new name.  */
3344   def_operand_p def_p;
3345   ssa_op_iter op_iter;
3346   FOR_EACH_SSA_DEF_OPERAND (def_p, copy, op_iter, SSA_OP_ALL_DEFS)
3347     {
3348       tree old_name = DEF_FROM_PTR (def_p);
3349       tree new_name = create_new_def_for (old_name, copy, def_p);
3350       region->parameter_rename_map->put(old_name, new_name);
3351     }
3352
3353   update_stmt (copy);
3354 }
3355
3356 static void
3357 copy_internal_parameters (sese_info_p region, sese_info_p to_region)
3358 {
3359   /* For all the parameters which definitino is in the if_region->false_region,
3360      insert code on true_region (if_region->true_region->entry). */
3361
3362   int i;
3363   tree tr;
3364   gimple_stmt_iterator gsi = gsi_start_bb(to_region->region.entry->dest);
3365
3366   FOR_EACH_VEC_ELT (region->params, i, tr)
3367     {
3368       // If def is not in region.
3369       gimple *def_stmt = SSA_NAME_DEF_STMT (tr);
3370       if (def_stmt)
3371         copy_def (tr, def_stmt, region, to_region, &gsi);
3372     }
3373 }
3374
3375 /* GIMPLE Loop Generator: generates loops from STMT in GIMPLE form for
3376    the given SCOP.  Return true if code generation succeeded.
3377
3378    FIXME: This is not yet a full implementation of the code generator
3379    with isl ASTs.  Generation of GIMPLE code has to be completed.  */
3380
3381 bool
3382 graphite_regenerate_ast_isl (scop_p scop)
3383 {
3384   sese_info_p region = scop->scop_info;
3385   translate_isl_ast_to_gimple t (region);
3386
3387   ifsese if_region = NULL;
3388   isl_ast_node *root_node;
3389   ivs_params ip;
3390
3391   timevar_push (TV_GRAPHITE_CODE_GEN);
3392   root_node = t.scop_to_isl_ast (scop, ip);
3393
3394   if (dump_file && (dump_flags & TDF_DETAILS))
3395     {
3396       fprintf (dump_file, "AST generated by isl: \n");
3397       t.print_isl_ast_node (dump_file, root_node, scop->isl_context);
3398     }
3399
3400   recompute_all_dominators ();
3401   graphite_verify ();
3402
3403   if_region = move_sese_in_condition (region);
3404   region->if_region = if_region;
3405   recompute_all_dominators ();
3406
3407   loop_p context_loop = region->region.entry->src->loop_father;
3408
3409   /* Copy all the parameters which are defined in the region.  */
3410   copy_internal_parameters(if_region->false_region, if_region->true_region);
3411
3412   edge e = single_succ_edge (if_region->true_region->region.entry->dest);
3413   basic_block bb = split_edge (e);
3414
3415   /* Update the true_region exit edge.  */
3416   region->if_region->true_region->region.exit = single_succ_edge (bb);
3417
3418   t.translate_isl_ast (context_loop, root_node, e, ip);
3419   if (t.codegen_error_p ())
3420     {
3421       if (dump_file)
3422         fprintf (dump_file, "[codegen] unsuccessful,"
3423                  " reverting back to the original code.\n");
3424       set_ifsese_condition (if_region, integer_zero_node);
3425     }
3426   else
3427     {
3428       t.translate_pending_phi_nodes ();
3429       if (!t.codegen_error_p ())
3430         {
3431           sese_insert_phis_for_liveouts (region,
3432                                          if_region->region->region.exit->src,
3433                                          if_region->false_region->region.exit,
3434                                          if_region->true_region->region.exit);
3435           mark_virtual_operands_for_renaming (cfun);
3436           update_ssa (TODO_update_ssa);
3437
3438
3439           graphite_verify ();
3440           scev_reset ();
3441           recompute_all_dominators ();
3442           graphite_verify ();
3443         }
3444       else
3445         {
3446           if (dump_file)
3447             fprintf (dump_file, "[codegen] unsuccessful in translating"
3448                      " pending phis, reverting back to the original code.\n");
3449           set_ifsese_condition (if_region, integer_zero_node);
3450         }
3451     }
3452
3453   free (if_region->true_region);
3454   free (if_region->region);
3455   free (if_region);
3456
3457   ivs_params_clear (ip);
3458   isl_ast_node_free (root_node);
3459   timevar_pop (TV_GRAPHITE_CODE_GEN);
3460
3461   if (dump_file && (dump_flags & TDF_DETAILS))
3462     {
3463       loop_p loop;
3464       int num_no_dependency = 0;
3465
3466       FOR_EACH_LOOP (loop, 0)
3467         if (loop->can_be_parallel)
3468           num_no_dependency++;
3469
3470       fprintf (dump_file, "%d loops carried no dependency.\n",
3471                num_no_dependency);
3472     }
3473
3474   return !t.codegen_error_p ();
3475 }
3476
3477 #endif  /* HAVE_isl */