public inbox for fortran@gcc.gnu.org
 help / color / mirror / Atom feed
From: Thomas Koenig <tkoenig@netcologne.de>
To: Jakub Jelinek <jakub@redhat.com>
Cc: sgk@troutmask.apl.washington.edu,
	"fortran@gcc.gnu.org" <fortran@gcc.gnu.org>,
	gcc-patches <gcc-patches@gcc.gnu.org>
Subject: Re: [patch, fortran] Remove parallell annotation from DO CONCURRENT
Date: Wed, 11 Apr 2018 18:18:00 -0000	[thread overview]
Message-ID: <8d3541f6-ecc5-66d1-d59c-d5b5c4b8f8a6@netcologne.de> (raw)
In-Reply-To: <20180411154423.GU8577@tucnak>

[-- Attachment #1: Type: text/plain, Size: 1602 bytes --]

Am 11.04.2018 um 17:44 schrieb Jakub Jelinek:
> On Tue, Apr 10, 2018 at 11:50:44PM +0200, Thomas Koenig wrote:
>> Hi Jakub,
>>
>>
>>> The new test FAILs everywhere, gfortran.dg doesn't have infrastructure to
>>> run -fopenmp, -fopenacc nor -ftree-parallelize-loops= tests.
>>> You need to put such tests into libgomp/testsuite/libgomp.fortran/
>>
>> I put the test case in the attached form into the libgomp.fortran
>> directory, but it failed execution, without error message.
>>
>> Anything I could have done differently?
> 
> Avoid using that much stack?

Well, I don't think stack use is excessive :-)

$ gfortran -S -Ofast do_concurrent_5.f90
$ fgrep ', %rsp' do_concurrent_5.s
         subq    $136, %rsp
         addq    $136, %rsp

I do see your point about total memory consumption, though.

Computation time of the test case I committed is around 1 s, which was
also not too bad.

I have attached updated patch which moves the test case to
gfortran.dg/gomp (where it actually passes).

Also, the patch below implements the suggestion of using
annot_expr_ivdep_kind.

OK for trunk?

Regards

	Thomas

2018-04-11  Thomas Koenig  <tkoenig@gcc.gnu.org>

	PR fortran/83064
	PR testsuite/85346
	* trans-stmt.c (gfc_trans_forall_loop): Use annot_expr_ivdep_kind
	for annotation and remove dependence on -ftree-parallelize-loops.

2018-04-11  Thomas Koenig  <tkoenig@gcc.gnu.org>

	PR fortran/83064
	PR testsuite/85346
	* gfortran.dg/do_concurrent_5.f90: Reduce memory consumption and
	move test to
	* gfortran.dg/gomp/do_concurrent_5.f90: New location.
	* gfortran.dg/do_concurrent_6.f90: New test.

[-- Attachment #2: p5.diff --]
[-- Type: text/x-patch, Size: 6382 bytes --]

Index: fortran/trans-stmt.c
===================================================================
--- fortran/trans-stmt.c	(Revision 259326)
+++ fortran/trans-stmt.c	(Arbeitskopie)
@@ -3643,12 +3643,12 @@
       cond = fold_build2_loc (input_location, LE_EXPR, logical_type_node,
 			      count, build_int_cst (TREE_TYPE (count), 0));
 
-      /* PR 83064 means that we cannot use the annotation if the
-	 autoparallelizer is active.  */
-      if (forall_tmp->do_concurrent && ! flag_tree_parallelize_loops)
+      /* PR 83064 means that we cannot use annot_expr_parallel_kind until
+       the autoparallelizer can hande this.  */
+      if (forall_tmp->do_concurrent)
 	cond = build3 (ANNOTATE_EXPR, TREE_TYPE (cond), cond,
 		       build_int_cst (integer_type_node,
-				      annot_expr_parallel_kind),
+				      annot_expr_ivdep_kind),
 		       integer_zero_node);
 
       tmp = build1_v (GOTO_EXPR, exit_label);
Index: testsuite/gfortran.dg/do_concurrent_5.f90
===================================================================
--- testsuite/gfortran.dg/do_concurrent_5.f90	(Revision 259258)
+++ testsuite/gfortran.dg/do_concurrent_5.f90	(nicht existent)
@@ -1,70 +0,0 @@
-! { dg-do  run }
-! PR 83064 - this used to give wrong results.
-! { dg-options "-O3 -ftree-parallelize-loops=2" }
-! Original test case by Christian Felter
-
-program main
-    use, intrinsic :: iso_fortran_env
-    implicit none
-
-    integer, parameter :: nsplit = 4
-    integer(int64), parameter :: ne = 20000000
-    integer(int64) :: stride, low(nsplit), high(nsplit), edof(ne), i
-    real(real64), dimension(nsplit) :: pi
-    
-    edof(1::4) = 1
-    edof(2::4) = 2
-    edof(3::4) = 3
-    edof(4::4) = 4
-    
-    stride = ceiling(real(ne)/nsplit)
-    do i = 1, nsplit
-        high(i) = stride*i
-    end do
-    do i = 2, nsplit
-        low(i) = high(i-1) + 1
-    end do
-    low(1) = 1
-    high(nsplit) = ne
-
-    pi = 0
-    do concurrent (i = 1:nsplit)
-        pi(i) = sum(compute( low(i), high(i) ))
-    end do
-    if (abs (sum(pi) - atan(1.0d0)) > 1e-5) call abort
-    
-contains
-    
-    pure function compute( low, high ) result( ttt )        
-        integer(int64), intent(in) :: low, high
-        real(real64), dimension(nsplit) :: ttt
-        integer(int64) :: j, k
-        
-        ttt = 0
-
-        ! Unrolled loop
-!         do j = low, high, 4
-!             k = 1
-!             ttt(k) = ttt(k) + (-1)**(j+1) / real( 2*j-1 )                            
-!             k = 2
-!             ttt(k) = ttt(k) + (-1)**(j+2) / real( 2*j+1 )                            
-!             k = 3
-!             ttt(k) = ttt(k) + (-1)**(j+3) / real( 2*j+3 )                            
-!             k = 4
-!             ttt(k) = ttt(k) + (-1)**(j+4) / real( 2*j+5 )                            
-!         end do
-        
-        ! Loop with modulo operation
-!         do j = low, high
-!             k = mod( j, nsplit ) + 1
-!             ttt(k) = ttt(k) + (-1)**(j+1) / real( 2*j-1 )                                        
-!         end do
-        
-        ! Loop with subscripting via host association
-        do j = low, high
-            k = edof(j)
-            ttt(k) = ttt(k) + (-1.0_real64)**(j+1) / real( 2*j-1 )                                        
-        end do
-    end function
-    
-end program main
Index: testsuite/gfortran.dg/do_concurrent_6.f90
===================================================================
--- testsuite/gfortran.dg/do_concurrent_6.f90	(nicht existent)
+++ testsuite/gfortran.dg/do_concurrent_6.f90	(Arbeitskopie)
@@ -0,0 +1,13 @@
+! { dg-do compile }
+! { dg-additional-options "-fdump-tree-original" }
+
+program main
+  real, dimension(100) :: a,b
+  call random_number(a)
+  do concurrent (i=1:100)
+     b(i) = a(i)*a(i)
+  end do
+  print *,sum(a)
+end program main
+
+! { dg-final { scan-tree-dump-times "ivdep" 1 "original" } }
Index: testsuite/gfortran.dg/gomp/do_concurrent_5.f90
===================================================================
--- testsuite/gfortran.dg/gomp/do_concurrent_5.f90	(nicht existent)
+++ testsuite/gfortran.dg/gomp/do_concurrent_5.f90	(Arbeitskopie)
@@ -0,0 +1,71 @@
+! { dg-do  run }
+! PR 83064 - this used to give wrong results.
+! { dg-additional-options "-O1 -ftree-parallelize-loops=2" }
+! Original test case by Christian Felter
+
+program main
+    use, intrinsic :: iso_fortran_env
+    implicit none
+
+    integer, parameter :: nsplit = 4
+    integer(int64), parameter :: ne = 2**20
+    integer(int64) :: stride, low(nsplit), high(nsplit), edof(ne), i
+    real(real64), dimension(nsplit) :: pi
+    
+    edof(1::4) = 1
+    edof(2::4) = 2
+    edof(3::4) = 3
+    edof(4::4) = 4
+    
+    stride = ceiling(real(ne)/nsplit)
+    do i = 1, nsplit
+        high(i) = stride*i
+    end do
+    do i = 2, nsplit
+        low(i) = high(i-1) + 1
+    end do
+    low(1) = 1
+    high(nsplit) = ne
+
+    pi = 0
+    do concurrent (i = 1:nsplit)
+        pi(i) = sum(compute( low(i), high(i) ))
+    end do
+    print *,sum(pi)
+    if (abs (sum(pi) - atan(1.0d0)) > 1e-5) STOP 1
+    
+contains
+    
+    pure function compute( low, high ) result( ttt )        
+        integer(int64), intent(in) :: low, high
+        real(real64), dimension(nsplit) :: ttt
+        integer(int64) :: j, k
+        
+        ttt = 0
+
+        ! Unrolled loop
+!         do j = low, high, 4
+!             k = 1
+!             ttt(k) = ttt(k) + (-1)**(j+1) / real( 2*j-1 )                            
+!             k = 2
+!             ttt(k) = ttt(k) + (-1)**(j+2) / real( 2*j+1 )                            
+!             k = 3
+!             ttt(k) = ttt(k) + (-1)**(j+3) / real( 2*j+3 )                            
+!             k = 4
+!             ttt(k) = ttt(k) + (-1)**(j+4) / real( 2*j+5 )                            
+!         end do
+        
+        ! Loop with modulo operation
+!         do j = low, high
+!             k = mod( j, nsplit ) + 1
+!             ttt(k) = ttt(k) + (-1)**(j+1) / real( 2*j-1 )                                        
+!         end do
+        
+        ! Loop with subscripting via host association
+        do j = low, high
+            k = edof(j)
+            ttt(k) = ttt(k) + (-1.0_real64)**(j+1) / real( 2*j-1 )                                        
+        end do
+    end function
+    
+end program main

  reply	other threads:[~2018-04-11 18:18 UTC|newest]

Thread overview: 15+ messages / expand[flat|nested]  mbox.gz  Atom feed  top
2018-04-09 20:10 Thomas Koenig
2018-04-09 20:28 ` Steve Kargl
2018-04-09 20:58   ` Thomas Koenig
2018-04-09 21:19     ` Steve Kargl
2018-04-10  6:44     ` Richard Biener
2018-04-10 13:36     ` Jakub Jelinek
2018-04-10 21:50       ` Thomas Koenig
2018-04-11 18:35         ` Jakub Jelinek
2018-04-11 18:18           ` Thomas Koenig [this message]
2018-04-11 18:35             ` Jakub Jelinek
2018-04-11 19:47               ` Thomas Koenig
2018-04-12  7:17                 ` Jakub Jelinek
2018-04-12 21:14                   ` Thomas Koenig
2018-04-12 21:35                     ` Jakub Jelinek
2018-04-09 23:35 ` Jakub Jelinek

Reply instructions:

You may reply publicly to this message via plain-text email
using any one of the following methods:

* Save the following mbox file, import it into your mail client,
  and reply-to-all from there: mbox

  Avoid top-posting and favor interleaved quoting:
  https://en.wikipedia.org/wiki/Posting_style#Interleaved_style

* Reply using the --to, --cc, and --in-reply-to
  switches of git-send-email(1):

  git send-email \
    --in-reply-to=8d3541f6-ecc5-66d1-d59c-d5b5c4b8f8a6@netcologne.de \
    --to=tkoenig@netcologne.de \
    --cc=fortran@gcc.gnu.org \
    --cc=gcc-patches@gcc.gnu.org \
    --cc=jakub@redhat.com \
    --cc=sgk@troutmask.apl.washington.edu \
    /path/to/YOUR_REPLY

  https://kernel.org/pub/software/scm/git/docs/git-send-email.html

* If your mail client supports setting the In-Reply-To header
  via mailto: links, try the mailto: link
Be sure your reply has a Subject: header at the top and a blank line before the message body.
This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).