public inbox for gcc-patches@gcc.gnu.org
 help / color / mirror / Atom feed
* [Patch][OpenMP] Fix 'omp exit data' for Fortran arrays (PR 94635)
@ 2020-04-17 15:54 Tobias Burnus
  2020-04-17 15:57 ` Tobias Burnus
  0 siblings, 1 reply; 7+ messages in thread
From: Tobias Burnus @ 2020-04-17 15:54 UTC (permalink / raw)
  To: gcc-patches, Jakub Jelinek

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

It turned out that doing
   omp enter data map(alloc:FortranArray)
   omp exit data map(delete:FortranArray)
left the array descriptor (fortranarray [as opposed to fortranarray.data])
on the device. (cf. -fdump-tree-omplower in the PR.)

Mapping FortranArray again (e.g. "map(tofrom:FortranArray)")
then failed by returning garbage.

This patch now removes the descriptor with 'data exit',
which was passed as MAP_TO_PSET clause to the middle end,
but got removed. Instead, the clause is now turned into MAP_DELETE.

Build on x86-64-gnu-linux and tested without and with AMDGCN
as offloading device. OK for the trunk?

Tobias

-----------------
Mentor Graphics (Deutschland) GmbH, Arnulfstraße 201, 80634 München / Germany
Registergericht München HRB 106955, Geschäftsführer: Thomas Heurung, Alexander Walter

[-- Attachment #2: test_target_enter_exit_data_allocate_array_alloc_delete.F90 --]
[-- Type: text/x-fortran, Size: 6570 bytes --]

!===--test_target_enter_exit_data_allocate_array_alloc_delete.F90 - alloc/delete--===!
! 
! OpenMP API Version 4.5 Nov 2015
!
! This tests covers the target enter/exit data with the
! map(alloc/delete) modifiers respectively, for arrays that have the
! allocatable modifier and that are dynamically generated. 
!
!!===----------------------------------------------------------------------===!
#include "ompvv.F90"

#define N 20

      PROGRAM tests_target_enter_exit_data_allocate_array_alloc
        USE iso_fortran_env
        USE ompvv_lib
        USE omp_lib
        implicit none
        INTEGER, ALLOCATABLE, DIMENSION(:) :: my1DPtr
        INTEGER, ALLOCATABLE, DIMENSION(:,:) :: my2DPtr
        INTEGER, ALLOCATABLE, DIMENSION(:,:,:) :: my3DPtr
        ! Helper arrays
        INTEGER, DIMENSION(N) :: my1DArr
        INTEGER, DIMENSION(N,N) :: my2DArr
        INTEGER, DIMENSION(N,N,N) :: my3DArr
        ! Helper functions
        LOGICAL :: isSharedEnv
        CHARACTER (len = 400) :: helperMsg
        INTEGER :: errors, i
      
        OMPVV_TEST_OFFLOADING
        OMPVV_TEST_AND_SET_SHARED_ENVIRONMENT(isSharedEnv)

        WRITE(helperMsg, *) "Omitting part of the test due to &
          &shared data environment"
        OMPVV_WARNING_IF(isSharedEnv, helperMsg)

        OMPVV_TEST_VERBOSE(test_allocate_array1D_map_alloc() .ne. 0)
        OMPVV_TEST_VERBOSE(test_allocate_array2D_map_alloc() .ne. 0)
        OMPVV_TEST_VERBOSE(test_allocate_array3D_map_alloc() .ne. 0)

        OMPVV_REPORT_AND_RETURN()


        CONTAINS 
          ! 1D Array test
          INTEGER FUNCTION test_allocate_array1D_map_alloc()

            OMPVV_INFOMSG("Testing map alloc/delete allocated 1D array")
            errors = 0
            ! Allocate the arrays
            allocate(my1DPtr(N))

            ! initialize 
            my1DPtr(:) = 0

            ! Mapping the array
            !$omp target enter data map(alloc: my1DPtr(:))

            ! Assign a value to the allocated space
            !$omp target
              my1DPtr(:) = (/ (i , i = 1,N) /)
            !$omp end target

            ! Confirm mapping with target region
            !$omp target map(from: my1DArr) 
              my1DArr = my1DPtr
            !$omp end target

            IF (.NOT. isSharedEnv) THEN
              ! Make sure data does not get transfered over the host
              OMPVV_TEST_AND_SET_VERBOSE(errors, ANY(my1DPtr /= 0))
            END IF
            OMPVV_TEST_AND_SET_VERBOSE(errors, SUM(my1DArr) /= ((N*(N+1)/2)))

            ! Asign a host value
            my1DPtr(:) = 10

            !$omp target exit data map(delete: my1DPtr(:))

            ! Check if I can transfer data with a map(tofrom:)
            !$omp target map(from: my1DArr) map(tofrom: my1DPtr(:))
              my1DArr = my1DPtr
              my1DPtr(:) = 20
            !$omp end target

            ! test that the values are the expected ones
            OMPVV_TEST_AND_SET_VERBOSE(errors, ANY(my1DPtr /= 20))
            OMPVV_TEST_AND_SET_VERBOSE(errors, ANY(my1DArr /= 10))

            deallocate(my1DPtr)

            test_allocate_array1D_map_alloc = errors

          END FUNCTION test_allocate_array1D_map_alloc
          ! 2D Array test
          INTEGER FUNCTION test_allocate_array2D_map_alloc()

            OMPVV_INFOMSG("Testing map alloc/delete allocated 2D array")
            errors = 0
            ! Allocate the arrays
            allocate(my2DPtr(N,N))

            ! initialize 
            my2DPtr(:,:) = 0

            ! Mapping the array
            !$omp target enter data map(alloc: my2DPtr(:,:))

            ! Assign a value to the allocated space
            !$omp target
              my2DPtr(:,:) = RESHAPE((/ (i , i = 1,N**2) /), (/ N,N /))
            !$omp end target

            ! Confirm mapping with target region
            !$omp target map(from: my2DArr) 
              my2DArr = my2DPtr
            !$omp end target


            IF (.NOT. isSharedEnv) THEN
              OMPVV_TEST_AND_SET_VERBOSE(errors, ANY(my2DPtr /= 0))
            END IF
            OMPVV_TEST_AND_SET_VERBOSE(errors, SUM(my2DArr) /= ((N**2*(N**2+1)/2)))

            ! Asign a host value
            my2DPtr(:,:) = 10

            !$omp target exit data map(delete: my2DPtr(:,:))

            ! Check if I can transfer data with a map(tofrom:)
            !$omp target map(from: my2DArr) map(tofrom: my2DPtr(:,:))
              my2DArr = my2DPtr
              my2DPtr(:,:) = 20
            !$omp end target

            ! test that the values are the expected ones
            OMPVV_TEST_AND_SET_VERBOSE(errors, ANY(my2DPtr /= 20))
            OMPVV_TEST_AND_SET_VERBOSE(errors, ANY(my2DArr /= 10))

            deallocate(my2DPtr)
            test_allocate_array2D_map_alloc = errors

          END FUNCTION test_allocate_array2D_map_alloc
          ! 3D Array test
          INTEGER FUNCTION test_allocate_array3D_map_alloc()

            OMPVV_INFOMSG("Testing map alloc/delete allocated 3D array")
            errors = 0
            ! Allocate the arrays
            allocate(my3DPtr(N,N,N))

            ! initialize 
            my3DPtr(:,:,:) = 0

            ! Mapping the array
            !$omp target enter data map(alloc: my3DPtr(:,:,:))

            ! Assign a value to the allocated space
            !$omp target
              my3DPtr(:,:,:) = RESHAPE((/ (i , i = 1,N**3) /), (/ N,N,N /))
            !$omp end target

            ! Confirm mapping with target region
            !$omp target map(from: my3DArr) 
              my3DArr = my3DPtr
            !$omp end target


            IF (.NOT. isSharedEnv) THEN
              OMPVV_TEST_AND_SET_VERBOSE(errors, ANY(my3DPtr /= 0))
            END IF
            OMPVV_TEST_AND_SET_VERBOSE(errors, SUM(my3DArr) /= ((N**3*(N**3+1)/2)))
            ! Asign a host value
            my3DPtr(:,:,:) = 10

            !$omp target exit data map(delete: my3DPtr(:,:,:))

            ! Check if I can transfer data with a map(tofrom:)
            !$omp target map(from: my3DArr) map(tofrom: my3DPtr(:,:,:))
              my3DArr = my3DPtr
              my3DPtr(:,:,:) = 20
            !$omp end target

            ! test that the values are the expected ones
            OMPVV_TEST_AND_SET_VERBOSE(errors, ANY(my3DPtr /= 20))
            OMPVV_TEST_AND_SET_VERBOSE(errors, ANY(my3DArr /= 10))

            deallocate(my3DPtr)

            test_allocate_array3D_map_alloc = errors

          END FUNCTION test_allocate_array3D_map_alloc
      END PROGRAM tests_target_enter_exit_data_allocate_array_alloc


^ permalink raw reply	[flat|nested] 7+ messages in thread

* Re: [Patch][OpenMP] Fix 'omp exit data' for Fortran arrays (PR 94635)
  2020-04-17 15:54 [Patch][OpenMP] Fix 'omp exit data' for Fortran arrays (PR 94635) Tobias Burnus
@ 2020-04-17 15:57 ` Tobias Burnus
  2020-04-17 16:33   ` Jakub Jelinek
  2020-04-20 21:33   ` Thomas Schwinge
  0 siblings, 2 replies; 7+ messages in thread
From: Tobias Burnus @ 2020-04-17 15:57 UTC (permalink / raw)
  To: gcc-patches, Jakub Jelinek

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

Next try – with the proper patch instead of a full test case.

On 4/17/20 5:54 PM, Tobias Burnus wrote:
> It turned out that doing
>   omp enter data map(alloc:FortranArray)
>   omp exit data map(delete:FortranArray)
> left the array descriptor (fortranarray [as opposed to
> fortranarray.data])
> on the device. (cf. -fdump-tree-omplower in the PR.)
>
> Mapping FortranArray again (e.g. "map(tofrom:FortranArray)")
> then failed by returning garbage.
>
> This patch now removes the descriptor with 'data exit',
> which was passed as MAP_TO_PSET clause to the middle end,
> but got removed. Instead, the clause is now turned into MAP_DELETE.
>
> Build on x86-64-gnu-linux and tested without and with AMDGCN
> as offloading device. OK for the trunk?
>
> Tobias
>
-----------------
Mentor Graphics (Deutschland) GmbH, Arnulfstraße 201, 80634 München / Germany
Registergericht München HRB 106955, Geschäftsführer: Thomas Heurung, Alexander Walter

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

[OpenMP] Fix 'omp exit data' for Fortran arrays (PR 94635)

	PR middle-end/94635
	* gimplify.c (gimplify_scan_omp_clauses): Turn MAP_TO_PSET to
	MAP_DELETE.

	PR middle-end/94635
	* testsuite/libgomp.fortran/target-enter-data-2.F90: New.

 gcc/gimplify.c                                     | 14 +++++---
 .../libgomp.fortran/target-enter-data-2.F90        | 40 ++++++++++++++++++++++
 2 files changed, 49 insertions(+), 5 deletions(-)

diff --git a/gcc/gimplify.c b/gcc/gimplify.c
index 8cdfae26510..6fd8196f01c 100644
--- a/gcc/gimplify.c
+++ b/gcc/gimplify.c
@@ -8785,11 +8785,15 @@ gimplify_scan_omp_clauses (tree *list_p, gimple_seq *pre_p,
 	     'exit data' - and in particular for 'delete:' - having an 'alloc:'
 	     does not make sense.  Likewise, for 'update' only transferring the
 	     data itself is needed as the rest has been handled in previous
-	     directives.  */
-	  if ((code == OMP_TARGET_EXIT_DATA || code == OMP_TARGET_UPDATE)
-	      && (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_POINTER
-		  || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_TO_PSET))
-	    remove = true;
+	     directives.  However, for 'exit data', the array descriptor needs
+	     to be delete; hence, we turn the MAP_TO_PSET into a MAP_DELETE.  */
+	  if (code == OMP_TARGET_EXIT_DATA
+	      && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_TO_PSET)
+	    OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_DELETE);
+	  else if ((code == OMP_TARGET_EXIT_DATA || code == OMP_TARGET_UPDATE)
+		   && (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_POINTER
+		       || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_TO_PSET))
+		remove = true;
 
 	  if (remove)
 	    break;
diff --git a/libgomp/testsuite/libgomp.fortran/target-enter-data-2.F90 b/libgomp/testsuite/libgomp.fortran/target-enter-data-2.F90
new file mode 100644
index 00000000000..320d8bf419f
--- /dev/null
+++ b/libgomp/testsuite/libgomp.fortran/target-enter-data-2.F90
@@ -0,0 +1,40 @@
+! { dg-additional-options "-DMEM_SHARED" { target offload_device_shared_as } }
+!
+! PR middle-end/94635
+  implicit none
+  integer, parameter :: N = 20
+  integer, allocatable, dimension(:) :: my1DPtr
+  integer, dimension(N) :: my1DArr
+  integer :: i
+
+  allocate(my1DPtr(N))
+  my1DPtr = 43
+
+  !$omp target enter data map(alloc: my1DPtr)
+    !$omp target
+      my1DPtr = [(i , i = 1, N)]
+    !$omp end target
+
+    !$omp target map(from: my1DArr) 
+      my1DArr = my1DPtr
+    !$omp end target
+  !$omp target exit data map(delete: my1DPtr)
+
+  if (any (my1DArr /= [(i, i = 1, N)])) stop 1
+#if MEM_SHARED
+  if (any (my1DArr /= my1DPtr)) stop 2
+#else
+  if (any (43 /= my1DPtr)) stop 3
+#endif
+
+  my1DPtr = [(2*N-i, i = 1, N)]
+  my1DArr = 42
+ 
+  !$omp target map(tofrom: my1DArr) map(tofrom: my1DPtr(:))
+    my1DArr = my1DPtr
+    my1DPtr = 20
+  !$omp end target
+
+  if (any (my1DArr /= [(2*N-i, i = 1, N)])) stop 4
+  if (any (20 /= my1DPtr)) stop 6
+end

^ permalink raw reply	[flat|nested] 7+ messages in thread

* Re: [Patch][OpenMP] Fix 'omp exit data' for Fortran arrays (PR 94635)
  2020-04-17 15:57 ` Tobias Burnus
@ 2020-04-17 16:33   ` Jakub Jelinek
  2020-04-20 21:33   ` Thomas Schwinge
  1 sibling, 0 replies; 7+ messages in thread
From: Jakub Jelinek @ 2020-04-17 16:33 UTC (permalink / raw)
  To: Tobias Burnus; +Cc: gcc-patches

On Fri, Apr 17, 2020 at 05:57:06PM +0200, Tobias Burnus wrote:
> --- a/gcc/gimplify.c
> +++ b/gcc/gimplify.c
> @@ -8785,11 +8785,15 @@ gimplify_scan_omp_clauses (tree *list_p, gimple_seq *pre_p,
>  	     'exit data' - and in particular for 'delete:' - having an 'alloc:'
>  	     does not make sense.  Likewise, for 'update' only transferring the
>  	     data itself is needed as the rest has been handled in previous
> -	     directives.  */
> -	  if ((code == OMP_TARGET_EXIT_DATA || code == OMP_TARGET_UPDATE)
> -	      && (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_POINTER
> -		  || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_TO_PSET))
> -	    remove = true;
> +	     directives.  However, for 'exit data', the array descriptor needs
> +	     to be delete; hence, we turn the MAP_TO_PSET into a MAP_DELETE.  */
> +	  if (code == OMP_TARGET_EXIT_DATA
> +	      && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_TO_PSET)
> +	    OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_DELETE);
> +	  else if ((code == OMP_TARGET_EXIT_DATA || code == OMP_TARGET_UPDATE)
> +		   && (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_POINTER
> +		       || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_TO_PSET))
> +		remove = true;

Wrong indentation of the last line, should be 1 tab + 4 spaces instead
of 2 tabs.
Otherwise LGTM, thanks.

	Jakub


^ permalink raw reply	[flat|nested] 7+ messages in thread

* Re: [Patch][OpenMP] Fix 'omp exit data' for Fortran arrays (PR 94635)
  2020-04-17 15:57 ` Tobias Burnus
  2020-04-17 16:33   ` Jakub Jelinek
@ 2020-04-20 21:33   ` Thomas Schwinge
  2020-04-23 13:43     ` Follow-up Patch – " Tobias Burnus
  1 sibling, 1 reply; 7+ messages in thread
From: Thomas Schwinge @ 2020-04-20 21:33 UTC (permalink / raw)
  To: Tobias Burnus, gcc-patches, Jakub Jelinek

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

Hi!

On 2020-04-17T17:57:06+0200, Tobias Burnus <tobias@codesourcery.com> wrote:
> On 4/17/20 5:54 PM, Tobias Burnus wrote:
>> It turned out that doing
>>   omp enter data map(alloc:FortranArray)
>>   omp exit data map(delete:FortranArray)
>> left the array descriptor (fortranarray [as opposed to
>> fortranarray.data])
>> on the device. (cf. -fdump-tree-omplower in the PR.)
>>
>> Mapping FortranArray again (e.g. "map(tofrom:FortranArray)")
>> then failed by returning garbage.
>>
>> This patch now removes the descriptor with 'data exit',
>> which was passed as MAP_TO_PSET clause to the middle end,
>> but got removed.

So this is a fix-up for trunk r277631 "Fortran/OpenMP] Don't create
"alloc:" for 'target exit data'".  (Also cross-referencing PR92929
"OpenACC/OpenMP 'target' 'exit data'/'update' optimizations".)

>> Instead, the clause is now turned into MAP_DELETE.

Really 'GOMP_MAP_DELETE', or should that rather be 'GOMP_MAP_RELEASE'?
Considering nested data regions, for example:

  - 'enter data' // Increment reference count.
  - 'enter data' // Increment reference count.
  - 'exit data' // Should not "delete" here, but just "release"?
  - 'exit data' // Here, reference count the is zero, so "release" then equals "delete".

(I have neither tested this, not fully thought that through, especially
in context of (a) OpenMP, and (b) Fortran.)  ;-)


> --- /dev/null
> +++ b/libgomp/testsuite/libgomp.fortran/target-enter-data-2.F90
> @@ -0,0 +1,40 @@
> +! { dg-additional-options "-DMEM_SHARED" { target offload_device_shared_as } }
> +!
> +! PR middle-end/94635
> +  implicit none

As obvious, pushed the attached to master branch in commit
3f5d94c192b81a3868f32f309dadd5571ef51cdf "Add 'dg-do run' to
'libgomp.fortran/target-enter-data-2.F90'", see attached.


Grüße
 Thomas


-----------------
Mentor Graphics (Deutschland) GmbH, Arnulfstraße 201, 80634 München / Germany
Registergericht München HRB 106955, Geschäftsführer: Thomas Heurung, Alexander Walter

[-- Warning: decoded text below may be mangled, UTF-8 assumed --]
[-- Attachment #2: 0001-Add-dg-do-run-to-libgomp.fortran-target-enter-data-2.patch --]
[-- Type: text/x-diff, Size: 1487 bytes --]

From 3f5d94c192b81a3868f32f309dadd5571ef51cdf Mon Sep 17 00:00:00 2001
From: Thomas Schwinge <thomas@codesourcery.com>
Date: Mon, 20 Apr 2020 16:15:07 +0200
Subject: [PATCH] Add 'dg-do run' to 'libgomp.fortran/target-enter-data-2.F90'

Fix-up for commit af557050fd011a03d21dc26b31959033061a0443 "[OpenMP] Fix 'omp
exit data' for Fortran arrays (PR 94635)".

	libgomp/
	PR middle-end/94635
	* testsuite/libgomp.fortran/target-enter-data-2.F90: Add 'dg-do
	run'.
---
 libgomp/ChangeLog                                         | 6 ++++++
 libgomp/testsuite/libgomp.fortran/target-enter-data-2.F90 | 1 +
 2 files changed, 7 insertions(+)

diff --git a/libgomp/ChangeLog b/libgomp/ChangeLog
index b1cf297a0d7..c524abbbfb6 100644
--- a/libgomp/ChangeLog
+++ b/libgomp/ChangeLog
@@ -1,3 +1,9 @@
+2020-04-20  Thomas Schwinge  <thomas@codesourcery.com>
+
+	PR middle-end/94635
+	* testsuite/libgomp.fortran/target-enter-data-2.F90: Add 'dg-do
+	run'.
+
 2020-04-20  Tobias Burnus  <tobias@codesourcery.com>
 
 	PR middle-end/94120
diff --git a/libgomp/testsuite/libgomp.fortran/target-enter-data-2.F90 b/libgomp/testsuite/libgomp.fortran/target-enter-data-2.F90
index 320d8bf419f..36a2ed5ef11 100644
--- a/libgomp/testsuite/libgomp.fortran/target-enter-data-2.F90
+++ b/libgomp/testsuite/libgomp.fortran/target-enter-data-2.F90
@@ -1,4 +1,5 @@
 ! { dg-additional-options "-DMEM_SHARED" { target offload_device_shared_as } }
+! { dg-do run }
 !
 ! PR middle-end/94635
   implicit none
-- 
2.17.1


^ permalink raw reply	[flat|nested] 7+ messages in thread

* Follow-up Patch – Re: [Patch][OpenMP] Fix 'omp exit data' for Fortran arrays (PR 94635)
  2020-04-20 21:33   ` Thomas Schwinge
@ 2020-04-23 13:43     ` Tobias Burnus
  2020-05-05 16:36       ` *ping* | " Tobias Burnus
  2020-05-12 10:48       ` Jakub Jelinek
  0 siblings, 2 replies; 7+ messages in thread
From: Tobias Burnus @ 2020-04-23 13:43 UTC (permalink / raw)
  To: gcc-patches, Jakub Jelinek; +Cc: Thomas Schwinge

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

On 4/20/20 11:33 PM, Thomas Schwinge wrote:
> Really 'GOMP_MAP_DELETE', or should that rather be 'GOMP_MAP_RELEASE'?

Depends on the previous item, i.e. 'delete:' vs. 'release:/from:/…'

Rather obvious – OK?

Tobias

-----------------
Mentor Graphics (Deutschland) GmbH, Arnulfstraße 201, 80634 München / Germany
Registergericht München HRB 106955, Geschäftsführer: Thomas Heurung, Alexander Walter

[-- Attachment #2: exit_data-fixes.diff --]
[-- Type: text/x-patch, Size: 2284 bytes --]

[OpenMP] Fix 'omp exit data' for Fortran arrays (PR 94635)

	PR middle-end/94635
	* gimplify.c (gimplify_scan_omp_clauses): For MAP_TO_PSET with
	OMP_TARGET_EXIT_DATA, use 'release:' unless the associated
	item is 'delete:'.

	PR middle-end/94635
	* gfortran.dg/gomp/target-exit-data.f90: New.

 gcc/gimplify.c                                      |  4 +++-
 gcc/testsuite/gfortran.dg/gomp/target-exit-data.f90 | 20 ++++++++++++++++++++
 2 files changed, 23 insertions(+), 1 deletion(-)

diff --git a/gcc/gimplify.c b/gcc/gimplify.c
index 2f2c51b2d89..0bac9900210 100644
--- a/gcc/gimplify.c
+++ b/gcc/gimplify.c
@@ -8789,7 +8789,9 @@ gimplify_scan_omp_clauses (tree *list_p, gimple_seq *pre_p,
 	     to be delete; hence, we turn the MAP_TO_PSET into a MAP_DELETE.  */
 	  if (code == OMP_TARGET_EXIT_DATA
 	      && OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_TO_PSET)
-	    OMP_CLAUSE_SET_MAP_KIND (c, GOMP_MAP_DELETE);
+	    OMP_CLAUSE_SET_MAP_KIND (c, OMP_CLAUSE_MAP_KIND (*prev_list_p)
+					== GOMP_MAP_DELETE
+					? GOMP_MAP_DELETE : GOMP_MAP_RELEASE);
 	  else if ((code == OMP_TARGET_EXIT_DATA || code == OMP_TARGET_UPDATE)
 		   && (OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_POINTER
 		       || OMP_CLAUSE_MAP_KIND (c) == GOMP_MAP_TO_PSET))
diff --git a/gcc/testsuite/gfortran.dg/gomp/target-exit-data.f90 b/gcc/testsuite/gfortran.dg/gomp/target-exit-data.f90
new file mode 100644
index 00000000000..ed57d0072d7
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/gomp/target-exit-data.f90
@@ -0,0 +1,20 @@
+! { dg-do compile }
+! { dg-additional-options "-fdump-tree-omplower" }
+!
+! PR middle-end/94635
+
+integer, allocatable :: one(:), two(:), three(:)
+
+!$omp target enter data map(alloc:one)
+!$omp target enter data map(alloc:two)
+!$omp target enter data map(to:three)
+
+! ...
+!$omp target exit data map(delete:one)
+!$omp target exit data map(release:two)
+!$omp target exit data map(from:three)
+end
+
+! { dg-final { scan-tree-dump "omp target exit data map\\(delete:.*\\) map\\(delete:one \\\[len: .*\\\]\\)" "omplower" } }
+! { dg-final { scan-tree-dump "omp target exit data map\\(release:.*\\) map\\(release:two \\\[len: .*\\\]\\)" "omplower" } }
+! { dg-final { scan-tree-dump "omp target exit data map\\(from:.*\\) map\\(release:three \\\[len: .*\\\]\\)" "omplower" } }

^ permalink raw reply	[flat|nested] 7+ messages in thread

* *ping* | Re: Follow-up Patch – Re: [Patch][OpenMP] Fix 'omp exit data' for Fortran arrays (PR 94635)
  2020-04-23 13:43     ` Follow-up Patch – " Tobias Burnus
@ 2020-05-05 16:36       ` Tobias Burnus
  2020-05-12 10:48       ` Jakub Jelinek
  1 sibling, 0 replies; 7+ messages in thread
From: Tobias Burnus @ 2020-05-05 16:36 UTC (permalink / raw)
  To: gcc-patches, Jakub Jelinek; +Cc: Thomas Schwinge

OK for mainline and (once it opens) the GCC 10 branch?

This is a simple & quick to review patch.

Tobias

On 4/23/20 3:43 PM, Tobias Burnus wrote:

> On 4/20/20 11:33 PM, Thomas Schwinge wrote:
>> Really 'GOMP_MAP_DELETE', or should that rather be 'GOMP_MAP_RELEASE'?
>
> Depends on the previous item, i.e. 'delete:' vs. 'release:/from:/…'
>
> Rather obvious – OK?
>
> Tobias
>
-----------------
Mentor Graphics (Deutschland) GmbH, Arnulfstraße 201, 80634 München / Germany
Registergericht München HRB 106955, Geschäftsführer: Thomas Heurung, Alexander Walter

^ permalink raw reply	[flat|nested] 7+ messages in thread

* Re: Follow-up Patch – Re: [Patch][OpenMP] Fix 'omp exit data' for Fortran arrays (PR 94635)
  2020-04-23 13:43     ` Follow-up Patch – " Tobias Burnus
  2020-05-05 16:36       ` *ping* | " Tobias Burnus
@ 2020-05-12 10:48       ` Jakub Jelinek
  1 sibling, 0 replies; 7+ messages in thread
From: Jakub Jelinek @ 2020-05-12 10:48 UTC (permalink / raw)
  To: Tobias Burnus; +Cc: gcc-patches, Thomas Schwinge

On Thu, Apr 23, 2020 at 03:43:47PM +0200, Tobias Burnus wrote:
> On 4/20/20 11:33 PM, Thomas Schwinge wrote:
> > Really 'GOMP_MAP_DELETE', or should that rather be 'GOMP_MAP_RELEASE'?
> 
> Depends on the previous item, i.e. 'delete:' vs. 'release:/from:/…'
> 
> Rather obvious – OK?
> 
> Tobias
> 
> -----------------
> Mentor Graphics (Deutschland) GmbH, Arnulfstraße 201, 80634 München / Germany
> Registergericht München HRB 106955, Geschäftsführer: Thomas Heurung, Alexander Walter

> [OpenMP] Fix 'omp exit data' for Fortran arrays (PR 94635)
> 
> 	PR middle-end/94635
> 	* gimplify.c (gimplify_scan_omp_clauses): For MAP_TO_PSET with
> 	OMP_TARGET_EXIT_DATA, use 'release:' unless the associated
> 	item is 'delete:'.
> 
> 	PR middle-end/94635
> 	* gfortran.dg/gomp/target-exit-data.f90: New.

Ok, thanks.

	Jakub


^ permalink raw reply	[flat|nested] 7+ messages in thread

end of thread, other threads:[~2020-05-12 10:48 UTC | newest]

Thread overview: 7+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2020-04-17 15:54 [Patch][OpenMP] Fix 'omp exit data' for Fortran arrays (PR 94635) Tobias Burnus
2020-04-17 15:57 ` Tobias Burnus
2020-04-17 16:33   ` Jakub Jelinek
2020-04-20 21:33   ` Thomas Schwinge
2020-04-23 13:43     ` Follow-up Patch – " Tobias Burnus
2020-05-05 16:36       ` *ping* | " Tobias Burnus
2020-05-12 10:48       ` Jakub Jelinek

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).