summaryrefslogtreecommitdiff
path: root/gcc/graphite-clast-to-gimple.c
diff options
context:
space:
mode:
authorSebastian Pop <sebastian.pop@amd.com>2010-04-06 21:01:16 +0000
committerSebastian Pop <spop@gcc.gnu.org>2010-04-06 21:01:16 +0000
commitbd32f344edf8c50779ab8822236f1577a7649a1d (patch)
tree751c4be7e18b7af38104e63398dfecbec419be08 /gcc/graphite-clast-to-gimple.c
parent79d03cf81ba8c9c303a24e98e26ca0396355e0bd (diff)
downloadgcc-bd32f344edf8c50779ab8822236f1577a7649a1d.tar.gz
Compute min and max bounds for IVs and infer types.
2010-04-04 Sebastian Pop <sebastian.pop@amd.com> PR middle-end/43519 * Makefile.in (graphite-clast-to-gimple.o): Depends on langhooks.h. * graphite-clast-to-gimple.c: Include langhooks.h. (max_signed_precision_type): New. (max_precision_type): Takes two types as arguments. (precision_for_value): New. (precision_for_interval): New. (gcc_type_for_interval): New. (gcc_type_for_value): New. (gcc_type_for_clast_term): New. (gcc_type_for_clast_red): New. (gcc_type_for_clast_bin): New. (gcc_type_for_clast_expr): Split up into several functions. (gcc_type_for_clast_eq): Rewritten. (compute_bounds_for_level): New. (compute_type_for_level_1): New. (compute_type_for_level): New. (gcc_type_for_cloog_iv): Removed. (gcc_type_for_iv_of_clast_loop): Rewritten. (graphite_create_new_loop): Compute the lower and upper bound types with gcc_type_for_clast_expr. (graphite_create_new_loop_guard): Same. (find_cloog_iv_in_expr): Removed. (compute_cloog_iv_types_1): Removed. (compute_cloog_iv_types): Removed. (gloog): Do not call compute_cloog_iv_types. * graphite-sese-to-poly.c (new_gimple_bb): Do not initialize GBB_CLOOG_IV_TYPES. (free_data_refs_aux): Do not free GBB_CLOOG_IV_TYPES. * sese.h (struct gimple_bb): Removed field cloog_iv_types. (GBB_CLOOG_IV_TYPES): Removed. * gcc.dg/graphite/run-id-pr42644.c: Call abort. From-SVN: r158026
Diffstat (limited to 'gcc/graphite-clast-to-gimple.c')
-rw-r--r--gcc/graphite-clast-to-gimple.c530
1 files changed, 297 insertions, 233 deletions
diff --git a/gcc/graphite-clast-to-gimple.c b/gcc/graphite-clast-to-gimple.c
index 819b9247533..6aab2a5521c 100644
--- a/gcc/graphite-clast-to-gimple.c
+++ b/gcc/graphite-clast-to-gimple.c
@@ -40,6 +40,7 @@ along with GCC; see the file COPYING3. If not see
#include "value-prof.h"
#include "pointer-set.h"
#include "gimple.h"
+#include "langhooks.h"
#include "sese.h"
#ifdef HAVE_cloog
@@ -223,13 +224,40 @@ clast_name_to_gcc (const char *name, sese region, VEC (tree, heap) *newivs,
return newivs_to_depth_to_newiv (newivs, index);
}
-/* Returns the maximal precision type for expressions E1 and E2. */
+/* Returns the signed maximal precision type for expressions TYPE1 and TYPE2. */
-static inline tree
-max_precision_type (tree e1, tree e2)
+static tree
+max_signed_precision_type (tree type1, tree type2)
+{
+ int p1 = TYPE_PRECISION (type1);
+ int p2 = TYPE_PRECISION (type2);
+ int precision = p1 > p2 ? p1 : p2;
+ tree type = lang_hooks.types.type_for_size (precision, false);
+
+ if (!type)
+ {
+ gloog_error = true;
+ return integer_type_node;
+ }
+ return type;
+}
+
+/* Returns the maximal precision type for expressions TYPE1 and TYPE2. */
+
+static tree
+max_precision_type (tree type1, tree type2)
{
- tree type1 = TREE_TYPE (e1);
- tree type2 = TREE_TYPE (e2);
+
+ if (POINTER_TYPE_P (type1))
+ return type1;
+
+ if (POINTER_TYPE_P (type2))
+ return type2;
+
+ if (!TYPE_UNSIGNED (type1)
+ || !TYPE_UNSIGNED (type2))
+ return max_signed_precision_type (type1, type2);
+
return TYPE_PRECISION (type1) > TYPE_PRECISION (type2) ? type1 : type2;
}
@@ -384,7 +412,168 @@ clast_to_gcc_expression (tree type, struct clast_expr *e,
return NULL_TREE;
}
-/* Returns the type for the expression E. */
+/* Return the precision needed to represent the value VAL. */
+
+static int
+precision_for_value (Value val)
+{
+ Value x, y, two;
+ int precision;
+
+ value_init (x);
+ value_init (y);
+ value_init (two);
+ value_set_si (x, 2);
+ value_assign (y, val);
+ value_set_si (two, 2);
+ precision = 1;
+
+ if (value_neg_p (y))
+ value_oppose (y, y);
+
+ while (value_gt (y, x))
+ {
+ value_multiply (x, x, two);
+ precision++;
+ }
+
+ value_clear (x);
+ value_clear (y);
+ value_clear (two);
+
+ return precision;
+}
+
+/* Return the precision needed to represent the values between LOW and
+ UP. */
+
+static int
+precision_for_interval (Value low, Value up)
+{
+ Value diff;
+ int precision;
+
+ gcc_assert (value_le (low, up));
+
+ value_init (diff);
+ value_subtract (diff, up, low);
+ precision = precision_for_value (diff);
+ value_clear (diff);
+
+ return precision;
+}
+
+/* Return a type that could represent the integer value VAL, or
+ otherwise return NULL_TREE. */
+
+static tree
+gcc_type_for_interval (Value low, Value up, tree old_type)
+{
+ bool unsigned_p = true;
+ int precision, prec_up, prec_int;
+ tree type;
+
+ gcc_assert (value_le (low, up));
+
+ /* Preserve the signedness of the old IV. */
+ if ((old_type && !TYPE_UNSIGNED (old_type))
+ || value_neg_p (low))
+ unsigned_p = false;
+
+ prec_up = precision_for_value (up);
+ prec_int = precision_for_interval (low, up);
+ precision = prec_up > prec_int ? prec_up : prec_int;
+
+ type = lang_hooks.types.type_for_size (precision, unsigned_p);
+ if (!type)
+ {
+ gloog_error = true;
+ return integer_type_node;
+ }
+
+ return type;
+}
+
+/* Return a type that could represent the integer value VAL, or
+ otherwise return NULL_TREE. */
+
+static tree
+gcc_type_for_value (Value val)
+{
+ return gcc_type_for_interval (val, val, NULL_TREE);
+}
+
+/* Return the type for the clast_term T used in STMT. */
+
+static tree
+gcc_type_for_clast_term (struct clast_term *t,
+ sese region, VEC (tree, heap) *newivs,
+ htab_t newivs_index, htab_t params_index)
+{
+ gcc_assert (t->expr.type == expr_term);
+
+ if (!t->var)
+ return gcc_type_for_value (t->val);
+
+ return TREE_TYPE (clast_name_to_gcc (t->var, region, newivs,
+ newivs_index, params_index));
+}
+
+static tree
+gcc_type_for_clast_expr (struct clast_expr *, sese,
+ VEC (tree, heap) *, htab_t, htab_t);
+
+/* Return the type for the clast_reduction R used in STMT. */
+
+static tree
+gcc_type_for_clast_red (struct clast_reduction *r, sese region,
+ VEC (tree, heap) *newivs,
+ htab_t newivs_index, htab_t params_index)
+{
+ int i;
+ tree type = NULL_TREE;
+
+ if (r->n == 1)
+ return gcc_type_for_clast_expr (r->elts[0], region, newivs,
+ newivs_index, params_index);
+
+ switch (r->type)
+ {
+ case clast_red_sum:
+ case clast_red_min:
+ case clast_red_max:
+ type = gcc_type_for_clast_expr (r->elts[0], region, newivs,
+ newivs_index, params_index);
+ for (i = 1; i < r->n; i++)
+ type = max_precision_type (type, gcc_type_for_clast_expr
+ (r->elts[i], region, newivs,
+ newivs_index, params_index));
+
+ return type;
+
+ default:
+ break;
+ }
+
+ gcc_unreachable ();
+ return NULL_TREE;
+}
+
+/* Return the type for the clast_binary B used in STMT. */
+
+static tree
+gcc_type_for_clast_bin (struct clast_binary *b,
+ sese region, VEC (tree, heap) *newivs,
+ htab_t newivs_index, htab_t params_index)
+{
+ tree l = gcc_type_for_clast_expr ((struct clast_expr *) b->LHS, region,
+ newivs, newivs_index, params_index);
+ tree r = gcc_type_for_value (b->RHS);
+ return max_signed_precision_type (l, r);
+}
+
+/* Returns the type for the CLAST expression E when used in statement
+ STMT. */
static tree
gcc_type_for_clast_expr (struct clast_expr *e,
@@ -394,45 +583,16 @@ gcc_type_for_clast_expr (struct clast_expr *e,
switch (e->type)
{
case expr_term:
- {
- struct clast_term *t = (struct clast_term *) e;
-
- if (t->var)
- return TREE_TYPE (clast_name_to_gcc (t->var, region, newivs,
- newivs_index, params_index));
- else
- return NULL_TREE;
- }
+ return gcc_type_for_clast_term ((struct clast_term *) e, region,
+ newivs, newivs_index, params_index);
case expr_red:
- {
- struct clast_reduction *r = (struct clast_reduction *) e;
-
- if (r->n == 1)
- return gcc_type_for_clast_expr (r->elts[0], region, newivs,
- newivs_index, params_index);
- else
- {
- int i;
- for (i = 0; i < r->n; i++)
- {
- tree type = gcc_type_for_clast_expr (r->elts[i], region,
- newivs, newivs_index,
- params_index);
- if (type)
- return type;
- }
- return NULL_TREE;
- }
- }
+ return gcc_type_for_clast_red ((struct clast_reduction *) e, region,
+ newivs, newivs_index, params_index);
case expr_bin:
- {
- struct clast_binary *b = (struct clast_binary *) e;
- struct clast_expr *lhs = (struct clast_expr *) b->LHS;
- return gcc_type_for_clast_expr (lhs, region, newivs,
- newivs_index, params_index);
- }
+ return gcc_type_for_clast_bin ((struct clast_binary *) e, region,
+ newivs, newivs_index, params_index);
default:
gcc_unreachable ();
@@ -448,13 +608,11 @@ gcc_type_for_clast_eq (struct clast_equation *cleq,
sese region, VEC (tree, heap) *newivs,
htab_t newivs_index, htab_t params_index)
{
- tree type = gcc_type_for_clast_expr (cleq->LHS, region, newivs,
- newivs_index, params_index);
- if (type)
- return type;
-
- return gcc_type_for_clast_expr (cleq->RHS, region, newivs, newivs_index,
- params_index);
+ tree l = gcc_type_for_clast_expr (cleq->LHS, region, newivs,
+ newivs_index, params_index);
+ tree r = gcc_type_for_clast_expr (cleq->RHS, region, newivs,
+ newivs_index, params_index);
+ return max_precision_type (l, r);
}
/* Translates a clast equation CLEQ to a tree. */
@@ -524,103 +682,117 @@ graphite_create_new_guard (sese region, edge entry_edge,
return exit_edge;
}
-/* Walks a CLAST and returns the first statement in the body of a
- loop. */
+/* Compute the lower bound LOW and upper bound UP for the induction
+ variable at LEVEL for the statement PBB, based on the transformed
+ scattering of PBB: T|I|G|Cst, with T the scattering transform, I
+ the iteration domain, and G the context parameters. */
-static struct clast_user_stmt *
-clast_get_body_of_loop (struct clast_stmt *stmt)
+static void
+compute_bounds_for_level (poly_bb_p pbb, int level, Value low, Value up)
{
- if (!stmt
- || CLAST_STMT_IS_A (stmt, stmt_user))
- return (struct clast_user_stmt *) stmt;
+ ppl_Pointset_Powerset_C_Polyhedron_t ps;
+ ppl_Linear_Expression_t le;
- if (CLAST_STMT_IS_A (stmt, stmt_for))
- return clast_get_body_of_loop (((struct clast_for *) stmt)->body);
+ combine_context_id_scat (&ps, pbb, false);
- if (CLAST_STMT_IS_A (stmt, stmt_guard))
- return clast_get_body_of_loop (((struct clast_guard *) stmt)->then);
+ /* Prepare the linear expression corresponding to the level that we
+ want to maximize/minimize. */
+ {
+ ppl_dimension_type dim = pbb_nb_scattering_transform (pbb)
+ + pbb_dim_iter_domain (pbb) + pbb_nb_params (pbb);
- if (CLAST_STMT_IS_A (stmt, stmt_block))
- return clast_get_body_of_loop (((struct clast_block *) stmt)->body);
+ ppl_new_Linear_Expression_with_dimension (&le, dim);
+ ppl_set_coef (le, 2 * level + 1, 1);
+ }
- gcc_unreachable ();
+ ppl_max_for_le_pointset (ps, le, up);
+ ppl_min_for_le_pointset (ps, le, low);
}
-/* Java does not initialize long_long_integer_type_node. */
-#define my_long_long (long_long_integer_type_node ? long_long_integer_type_node : ssizetype)
+/* Compute the type for the induction variable at LEVEL for the
+ statement PBB, based on the transformed schedule of PBB. OLD_TYPE
+ is the type of the old induction variable for that loop. */
-/* Given a CLOOG_IV, return the type that CLOOG_IV should have in GCC
- land. The selected type is big enough to include the original loop
- iteration variable, but signed to work with the subtractions CLooG
- may have introduced. If such a type is not available, we fail.
+static tree
+compute_type_for_level_1 (poly_bb_p pbb, int level, tree old_type)
+{
+ Value low, up;
+ tree type;
- TODO: Do not always return long_long, but the smallest possible
- type, that still holds the original type.
+ value_init (low);
+ value_init (up);
- TODO: Get the types using CLooG instead. This enables further
- optimizations, but needs CLooG support. */
+ compute_bounds_for_level (pbb, level, low, up);
+ type = gcc_type_for_interval (low, up, old_type);
+
+ value_clear (low);
+ value_clear (up);
+ return type;
+}
+
+/* Compute the type for the induction variable at LEVEL for the
+ statement PBB, based on the transformed schedule of PBB. */
static tree
-gcc_type_for_cloog_iv (const char *cloog_iv, gimple_bb_p gbb)
+compute_type_for_level (poly_bb_p pbb, int level)
{
- struct ivtype_map_elt_s tmp;
- PTR *slot;
-
- tmp.cloog_iv = cloog_iv;
- slot = htab_find_slot (GBB_CLOOG_IV_TYPES (gbb), &tmp, NO_INSERT);
+ tree oldiv = pbb_to_depth_to_oldiv (pbb, level);
+ tree type = TREE_TYPE (oldiv);
- if (slot && *slot)
+ if (type && POINTER_TYPE_P (type))
{
- tree type = ((ivtype_map_elt) *slot)->type;
- int type_precision = TYPE_PRECISION (type);
-
- /* Find the smallest signed type possible. */
- if (!TYPE_UNSIGNED (type))
- {
- if (type_precision <= TYPE_PRECISION (integer_type_node))
- return integer_type_node;
+#ifdef ENABLE_CHECKING
+ tree ctype = compute_type_for_level_1 (pbb, level, type);
- if (type_precision <= TYPE_PRECISION (long_integer_type_node))
- return long_integer_type_node;
+ /* In the case of a pointer type, check that after the loop
+ transform, the lower and the upper bounds of the type fit the
+ oldiv pointer type. */
+ gcc_assert (TYPE_PRECISION (type) >= TYPE_PRECISION (ctype)
+ && integer_zerop (lower_bound_in_type (ctype, ctype)));
+#endif
+ return type;
+ }
- if (type_precision <= TYPE_PRECISION (my_long_long))
- return my_long_long;
+ return compute_type_for_level_1 (pbb, level, type);
+}
- gcc_unreachable ();
- }
+/* Walks a CLAST and returns the first statement in the body of a
+ loop. */
- if (type_precision < TYPE_PRECISION (integer_type_node))
- return integer_type_node;
+static struct clast_user_stmt *
+clast_get_body_of_loop (struct clast_stmt *stmt)
+{
+ if (!stmt
+ || CLAST_STMT_IS_A (stmt, stmt_user))
+ return (struct clast_user_stmt *) stmt;
- if (type_precision < TYPE_PRECISION (long_integer_type_node))
- return long_integer_type_node;
+ if (CLAST_STMT_IS_A (stmt, stmt_for))
+ return clast_get_body_of_loop (((struct clast_for *) stmt)->body);
- if (type_precision < TYPE_PRECISION (my_long_long))
- return my_long_long;
+ if (CLAST_STMT_IS_A (stmt, stmt_guard))
+ return clast_get_body_of_loop (((struct clast_guard *) stmt)->then);
- /* There is no signed type available, that is large enough to hold the
- original value. */
- gcc_unreachable ();
- }
+ if (CLAST_STMT_IS_A (stmt, stmt_block))
+ return clast_get_body_of_loop (((struct clast_block *) stmt)->body);
- return my_long_long;
+ gcc_unreachable ();
}
-#undef my_long_long
-
-/* Returns the induction variable for the loop that gets translated to
- STMT. */
+/* Returns the type for the induction variable for the loop translated
+ from STMT_FOR. */
static tree
-gcc_type_for_iv_of_clast_loop (struct clast_for *stmt_for)
+gcc_type_for_iv_of_clast_loop (struct clast_for *stmt_for, int level,
+ tree lb_type, tree ub_type)
{
struct clast_stmt *stmt = (struct clast_stmt *) stmt_for;
struct clast_user_stmt *body = clast_get_body_of_loop (stmt);
- const char *cloog_iv = stmt_for->iterator;
CloogStatement *cs = body->statement;
poly_bb_p pbb = (poly_bb_p) cloog_statement_usr (cs);
- return gcc_type_for_cloog_iv (cloog_iv, PBB_BLACK_BOX (pbb));
+ return max_precision_type (lb_type, max_precision_type
+ (ub_type, compute_type_for_level (pbb,
+ level - 1)));
}
/* Creates a new LOOP corresponding to Cloog's STMT. Inserts an
@@ -635,9 +807,13 @@ static struct loop *
graphite_create_new_loop (sese region, edge entry_edge,
struct clast_for *stmt,
loop_p outer, VEC (tree, heap) **newivs,
- htab_t newivs_index, htab_t params_index)
+ htab_t newivs_index, htab_t params_index, int level)
{
- tree type = gcc_type_for_iv_of_clast_loop (stmt);
+ tree lb_type = gcc_type_for_clast_expr (stmt->LB, region, *newivs,
+ newivs_index, params_index);
+ tree ub_type = gcc_type_for_clast_expr (stmt->UB, region, *newivs,
+ newivs_index, params_index);
+ tree type = gcc_type_for_iv_of_clast_loop (stmt, level, lb_type, ub_type);
tree lb = clast_to_gcc_expression (type, stmt->LB, region, *newivs,
newivs_index, params_index);
tree ub = clast_to_gcc_expression (type, stmt->UB, region, *newivs,
@@ -837,7 +1013,11 @@ graphite_create_new_loop_guard (sese region, edge entry_edge,
{
tree cond_expr;
edge exit_edge;
- tree type = gcc_type_for_iv_of_clast_loop (stmt);
+ tree lb_type = gcc_type_for_clast_expr (stmt->LB, region, newivs,
+ newivs_index, params_index);
+ tree ub_type = gcc_type_for_clast_expr (stmt->UB, region, newivs,
+ newivs_index, params_index);
+ tree type = max_precision_type (lb_type, ub_type);
tree lb = clast_to_gcc_expression (type, stmt->LB, region, newivs,
newivs_index, params_index);
tree ub = clast_to_gcc_expression (type, stmt->UB, region, newivs,
@@ -882,7 +1062,8 @@ translate_clast_for_loop (sese region, loop_p context_loop,
{
struct loop *loop = graphite_create_new_loop (region, next_e, stmt,
context_loop, newivs,
- newivs_index, params_index);
+ newivs_index, params_index,
+ level);
edge last_e = single_exit (loop);
edge to_body = single_succ_edge (loop->header);
basic_block after = to_body->dest;
@@ -927,7 +1108,7 @@ translate_clast_for (sese region, loop_p context_loop, struct clast_for *stmt,
htab_t params_index)
{
edge last_e = graphite_create_new_loop_guard (region, next_e, stmt, *newivs,
- newivs_index, params_index);
+ newivs_index, params_index);
edge true_e = get_true_edge_from_guard_bb (next_e->dest);
edge false_e = get_false_edge_from_guard_bb (next_e->dest);
@@ -1045,122 +1226,6 @@ translate_clast (sese region, loop_p context_loop, struct clast_stmt *stmt,
bb_pbb_mapping, level, params_index);
}
-/* Returns the first cloog name used in EXPR. */
-
-static const char *
-find_cloog_iv_in_expr (struct clast_expr *expr)
-{
- struct clast_term *term = (struct clast_term *) expr;
- struct clast_reduction *red;
- int i;
-
- if (expr->type == expr_term)
- return term->var;
-
- if (expr->type != expr_red)
- return NULL;
-
- red = (struct clast_reduction *) expr;
- for (i = 0; i < red->n; i++)
- {
- const char *res = find_cloog_iv_in_expr (red->elts[i]);
-
- if (res)
- return res;
- }
-
- return NULL;
-}
-
-/* Build for USER_STMT a map between the CLAST induction variables and
- the corresponding GCC old induction variables. This information is
- stored on each GRAPHITE_BB. */
-
-static void
-compute_cloog_iv_types_1 (poly_bb_p pbb, struct clast_user_stmt *user_stmt)
-{
- gimple_bb_p gbb = PBB_BLACK_BOX (pbb);
- struct clast_stmt *t;
- int index = 0;
-
- for (t = user_stmt->substitutions; t; t = t->next, index++)
- {
- PTR *slot;
- struct ivtype_map_elt_s tmp;
- struct clast_expr *expr = (struct clast_expr *)
- ((struct clast_assignment *)t)->RHS;
-
- /* Create an entry (clast_var, type). */
- tmp.cloog_iv = find_cloog_iv_in_expr (expr);
- if (!tmp.cloog_iv)
- continue;
-
- slot = htab_find_slot (GBB_CLOOG_IV_TYPES (gbb), &tmp, INSERT);
-
- if (slot && !*slot)
- {
- tree oldiv = pbb_to_depth_to_oldiv (pbb, index);
- tree type = TREE_TYPE (oldiv);
- *slot = new_ivtype_map_elt (tmp.cloog_iv, type);
- }
- }
-}
-
-/* Walk the CLAST tree starting from STMT and build for each
- clast_user_stmt a map between the CLAST induction variables and the
- corresponding GCC old induction variables. This information is
- stored on each GRAPHITE_BB. */
-
-static void
-compute_cloog_iv_types (struct clast_stmt *stmt)
-{
- if (!stmt)
- return;
-
- if (CLAST_STMT_IS_A (stmt, stmt_root))
- goto next;
-
- if (CLAST_STMT_IS_A (stmt, stmt_user))
- {
- CloogStatement *cs = ((struct clast_user_stmt *) stmt)->statement;
- poly_bb_p pbb = (poly_bb_p) cloog_statement_usr (cs);
- gimple_bb_p gbb = PBB_BLACK_BOX (pbb);
-
- if (!GBB_CLOOG_IV_TYPES (gbb))
- GBB_CLOOG_IV_TYPES (gbb) = htab_create (10, ivtype_map_elt_info,
- eq_ivtype_map_elts, free);
-
- compute_cloog_iv_types_1 (pbb, (struct clast_user_stmt *) stmt);
- goto next;
- }
-
- if (CLAST_STMT_IS_A (stmt, stmt_for))
- {
- struct clast_stmt *s = ((struct clast_for *) stmt)->body;
- compute_cloog_iv_types (s);
- goto next;
- }
-
- if (CLAST_STMT_IS_A (stmt, stmt_guard))
- {
- struct clast_stmt *s = ((struct clast_guard *) stmt)->then;
- compute_cloog_iv_types (s);
- goto next;
- }
-
- if (CLAST_STMT_IS_A (stmt, stmt_block))
- {
- struct clast_stmt *s = ((struct clast_block *) stmt)->body;
- compute_cloog_iv_types (s);
- goto next;
- }
-
- gcc_unreachable ();
-
- next:
- compute_cloog_iv_types (stmt->next);
-}
-
/* Free the SCATTERING domain list. */
static void
@@ -1512,7 +1577,6 @@ gloog (scop_p scop, VEC (scop_p, heap) *scops, htab_t bb_pbb_mapping)
graphite_verify ();
context_loop = SESE_ENTRY (region)->src->loop_father;
- compute_cloog_iv_types (pc.stmt);
rename_map = htab_create (10, rename_map_elt_info, eq_rename_map_elts, free);
newivs_index = htab_create (10, clast_name_index_elt_info,
eq_clast_name_indexes, free);