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