[Fortran, OpenMP] Fix allocatable-components check (PR67311)
authorTobias Burnus <tobias@codesourcery.com>
Tue, 14 Jul 2020 10:55:53 +0000 (12:55 +0200)
committerTobias Burnus <tobias@codesourcery.com>
Tue, 14 Jul 2020 10:55:53 +0000 (12:55 +0200)
gcc/fortran/ChangeLog:

PR fortran/67311
* trans-openmp.c (gfc_has_alloc_comps): Return false also for
pointers to arrays.

libgomp/ChangeLog:

PR fortran/67311
* testsuite/libgomp.fortran/target-map-1.f90: New test.

gcc/fortran/trans-openmp.c
libgomp/testsuite/libgomp.fortran/target-map-1.f90 [new file with mode: 0644]

index 38e141d83603fb9948ebd1951ad10c78940b4979..b2645e723d510fcaf5fc29e3df36ffa4749ef2d8 100644 (file)
@@ -330,6 +330,11 @@ gfc_has_alloc_comps (tree type, tree decl)
        return false;
     }
 
+  if (GFC_DESCRIPTOR_TYPE_P (type)
+      && (GFC_TYPE_ARRAY_AKIND (type) == GFC_ARRAY_POINTER
+         || GFC_TYPE_ARRAY_AKIND (type) == GFC_ARRAY_POINTER_CONT))
+    return false;
+
   if (GFC_DESCRIPTOR_TYPE_P (type) || GFC_ARRAY_TYPE_P (type))
     type = gfc_get_element_type (type);
 
diff --git a/libgomp/testsuite/libgomp.fortran/target-map-1.f90 b/libgomp/testsuite/libgomp.fortran/target-map-1.f90
new file mode 100644 (file)
index 0000000..6107530
--- /dev/null
@@ -0,0 +1,41 @@
+! PR fortran/67311
+
+implicit none
+  TYPE myType
+    integer :: A
+    TYPE(myType), DIMENSION(:), POINTER :: x
+    TYPE(myType), DIMENSION(:), contiguous, POINTER :: y
+    integer :: B
+  END TYPE myType
+  call openmp_sub
+contains
+  subroutine openmp_sub
+    type(myType) :: argument
+
+    !$OMP PARALLEL DEFAULT(NONE) PRIVATE(argument)
+      argument%a = 5
+      argument%b = 7
+      call foo(argument)
+      if (.not.associated(argument%x) .or. size(argument%x) /= 2) stop 2
+      if (argument%a /= 8 .or. argument%b /= 9 &
+          .or. any(argument%x(:)%a /= [2, 3]) &
+          .or. any(argument%x(:)%b /= [9, 1])) stop 3
+      if (.not.associated(argument%y) .or. size(argument%y) /= 3) stop 4
+      if (any(argument%y(:)%a /= [11, 22, 33]) &
+          .or. any(argument%y(:)%b /= [44, 55, 66])) stop 5
+      deallocate (argument%x, argument%y)
+    !$OMP END PARALLEL
+  end subroutine openmp_sub
+  subroutine foo(x)
+    type(myType), intent(inout) :: x
+    !$omp declare target
+    if (x%a /= 5 .or. x%b /= 7) stop 1
+    x%a = 8; x%b = 9
+    allocate (x%x(2))
+    x%x(:)%a = [2, 3]
+    x%x(:)%b = [9, 1]
+    allocate (x%y(3))
+    x%y(:)%a = [11, 22, 33]
+    x%y(:)%b = [44, 55, 66]
+  end subroutine
+end