Hi Cesar!
This patch, which is derived from Ilmir Usmanov's work posted here
<https://gcc.gnu.org/ml/gcc-patches/2014-04/msg00027.html>, implements
the loop directive in openacc. The original patch is mostly intact,
Thank you!
I looked through the patch and found that you also added middle-end
part. I don't know a lot about middle-end, so, probably, Thomas could
review the part. However, there is a regression in middle-end.
About front-ends, especially fortran front-end:
I did disable support for do concurrent loops since openacc
2.0a supports fortran up to fortran 2003.
As I can see, you didn't remove helper code for DO CONCURRENT loops
transformation (see below).
@@ -12217,8 +12221,8 @@ c_parser_omp_for_loop (location_t loc, c_parser
*parser, enum tree_code code,
for (cl = clauses; cl; cl = OMP_CLAUSE_CHAIN (cl))
if (OMP_CLAUSE_CODE (cl) == OMP_CLAUSE_COLLAPSE)
{
- gcc_assert (code != OACC_LOOP);
- collapse = tree_to_shwi (OMP_CLAUSE_COLLAPSE_EXPR (cl));
+ //gcc_assert (code != OACC_LOOP);
I suppose you forgot to remove this comment.
+++ b/gcc/testsuite/gfortran.dg/goacc/loop-4.f95
@@ -0,0 +1,16 @@
+! { dg-do compile }
+! { dg-additional-options "-fdump-tree-original -std=f2008" }
+
+PROGRAM test
+ IMPLICIT NONE
+ INTEGER :: a(64), b(64), c(64), i, j, k
+ ! Must be replaced by three loops.
+ !$acc loop
+ DO CONCURRENT (i=1:64, j=1:64, k=1:64, i==j .and. j==k)
This test is obsolete. I think you should remove this testcase since you
are not supporting DO CONCURRENT loops.
+++ b/gcc/testsuite/gfortran.dg/goacc/loop-tree.f95
For this test you should update tree-pretty-print.c (I forgot this):
@@ -675,13 +675,13 @@ dump_omp_clause (pretty_printer *buffer, tree
clause, int spc, int flags)
case OMP_CLAUSE_WORKER:
pp_string (buffer, "worker(");
- dump_generic_node (buffer, OMP_CLAUSE_DECL (clause), spc, flags,
false);
+ dump_generic_node (buffer, OMP_CLAUSE_WORKER_EXPR (clause), spc,
flags, false);
pp_character(buffer, ')');
break;
case OMP_CLAUSE_VECTOR:
pp_string (buffer, "vector(");
- dump_generic_node (buffer, OMP_CLAUSE_DECL (clause), spc, flags,
false);
+ dump_generic_node (buffer, OMP_CLAUSE_VECTOR_EXPR (clause), spc,
flags, false);
pp_character(buffer, ')');
break;
+/* Recursively generate conditional expressions. */
+static tree
+gfc_trans_oacc_loop_generate_mask_conds (gfc_code *code, int collapse)
+{
+ if (collapse > 1)
+ return gfc_trans_oacc_loop_generate_mask_conds (code->block->next,
+ collapse - 1);
+ else
+ return gfc_trans_omp_code (code->block->next, true);
+}
+static tree
+gfc_trans_oacc_loop (gfc_code *code, stmtblock_t *pblock,
+ gfc_omp_clauses *loop_clauses)
+{
+ /* DO CONCURRENT specific vars. */
+ int nforloops = 0;
+ int current_for = 0;
+
+ if (collapse <= 0)
+ collapse = 1;
+
+ code = code->block->next;
+
+ if (code->op == EXEC_DO_CONCURRENT)
+ gfc_error ("!$ACC LOOP directive is unsupported on DO CONCURRENT %L",
+ &code->loc);
+
+ gcc_assert (code->op == EXEC_DO);
+
+ if (pblock == NULL)
+ {
+ gfc_start_block (&block);
+ pblock = █
+ }
+
+ /* Calculate number of required for loops. */
+ old_code = code;
+ for (i = 0; i < collapse; i++)
+ {
+ if (code->op == EXEC_DO)
+ nforloops++;
+ else
+ gcc_unreachable ();
+ code = code->block->next;
+ }
+ code = old_code;
+
+ /* Set the number of required for loops for collapse. */
+ /* FIXME: this is probably correct, but OMP_CLAUSE_COLLAPSE isn't supported
+ yet. */
+ loop_clauses->collapse = nforloops;
+
+ omp_clauses = gfc_trans_omp_clauses (pblock, loop_clauses, code->loc);
+
+ init = make_tree_vec (nforloops);
+ cond = make_tree_vec (nforloops);
+ incr = make_tree_vec (nforloops);
+
+ for (i = 0; i < collapse; i++)
+ {
+ if (code->op == EXEC_DO)
+ gfc_trans_oacc_loop_generate_for (pblock, &se, code->ext.iterator->var,
+ code->ext.iterator->start,
+ code->ext.iterator->end,
+ code->ext.iterator->step,
+ current_for++, &init, &cond, &incr,
+ &inits);
+ else
+ gcc_unreachable ();
+ if (i + 1 < collapse)
+ code = code->block->next;
+ }
+
+ if (pblock != &block)
+ {
+ pushlevel ();
+ gfc_start_block (&block);
+ }
This is complicated for simple DO loops. I think the following will be
enough (see gfc_trans_omp_do).
code = code->block->next;
+ if (code->op == EXEC_DO_CONCURRENT)
+ gfc_error ("!$ACC LOOP directive is unsupported on DO CONCURRENT %L",
+ &code->loc);
gcc_assert (code->op == EXEC_DO);
init = make_tree_vec (collapse);
cond = make_tree_vec (collapse);
incr = make_tree_vec (collapse);
if (pblock == NULL)
{
gfc_start_block (&block);
pblock = █
}
@@ -1817,13 +1818,9 @@ scan_sharing_clauses (tree clauses, omp_context *ctx)
case OMP_CLAUSE_PRIVATE:
case OMP_CLAUSE_FIRSTPRIVATE:
case OMP_CLAUSE_REDUCTION:
- if (is_gimple_omp_oacc_specifically (ctx->stmt))
- {
- sorry ("clause not supported yet");
- break;
- }
This change produces regression on parallel-tree.f95 testcase: ICE.
--
Ilmir.