Closed
Description
I have this data in my code:
integer(kind=INT32), parameter :: r=2
If I try to use r
inside an OpenMP parallel region with default(none)
on it, I get to choose between these two errors:
error: The DEFAULT(NONE) clause requires that 'r' must be listed in a data-sharing attribute clause
(when not specifying its data-sharing attribute)Error: Object ‘r’ is not a variable at (1)
(when specifying its data-sharing attribute)
I do not know what the OpenMP rules are to know if PARAMETER is treated like a compile-time literal the way a preprocessor definition is in C/C++, or if it's actually data, but one of these versions has to be correct.
Both GCC and Intel Fortran accept the first version and reject the second, which suggests that default(none)
should ignore the lack of data-sharing attributes on PARAMETER data.
Error 1
jhammond@nuclear:~/PRK/FORTRAN$ /usr/local/bin/flang -fopenmp -c r1.F90
error: Semantic errors in r1.F90
./r1.F90:27:24: error: The DEFAULT(NONE) clause requires that 'r' must be listed in a data-sharing attribute clause
call apply_stencil(r,n,A)
^
flang: in /home/jhammond/PRK/FORTRAN, flang-new failed with exit status 1: /usr/local/bin/flang-new -fc1 -fopenmp -module-suffix .f18.mod -fdebug-unparse -fno-analyzed-objects-for-unparse -fopenmp -c r1.F90
Error 2
jhammond@nuclear:~/PRK/FORTRAN$ /usr/local/bin/flang -fopenmp -c r2.F90
flang_unparsed_file_7fae7c76cd13_0.f90:18:39:
18 | !$OMP PARALLEL DEFAULT(NONE) SHARED(n,r,a,iterations) PRIVATE(i,j,k)
| 1
Error: Object ‘r’ is not a variable at (1)
flang: in /home/jhammond/PRK/FORTRAN, gfortran failed with exit status 1: gfortran -fopenmp -c -fopenmp -c r2.F90
r1.F90
program main
use iso_fortran_env
use omp_lib
implicit none
integer :: err
integer(kind=INT32) :: iterations
integer(kind=INT32) :: n
integer(kind=INT32), parameter :: r=2
real(kind=REAL64), allocatable :: A(:,:)
integer(kind=INT32) :: i, j, k
iterations = 1
n = 100
allocate( A(n,n), stat=err)
if (err .ne. 0) then
write(*,'(a,i3)') 'allocation returned ',err
stop 1
endif
!$omp parallel default(none) &
!$omp& shared(n,A,iterations) &
!$omp& private(i,j,k)
do k=0,iterations
call apply_stencil(r,n,A)
!$omp do
do j=1,n
do i=1,n
A(i,j) = r
enddo
enddo
!$omp end do
enddo
!$omp end parallel
deallocate( A )
end program main
r2.F90
program main
use iso_fortran_env
use omp_lib
implicit none
integer :: err
integer(kind=INT32) :: iterations
integer(kind=INT32) :: n
integer(kind=INT32), parameter :: r=2
real(kind=REAL64), allocatable :: A(:,:)
integer(kind=INT32) :: i, j, k
iterations = 1
n = 100
allocate( A(n,n), stat=err)
if (err .ne. 0) then
write(*,'(a,i3)') 'allocation returned ',err
stop 1
endif
!$omp parallel default(none) &
!$omp& shared(n,r,A,iterations) &
!$omp& private(i,j,k)
do k=0,iterations
call apply_stencil(r,n,A)
!$omp do
do j=1,n
do i=1,n
A(i,j) = r
enddo
enddo
!$omp end do
enddo
!$omp end parallel
deallocate( A )
end program main
Other compilers
GCC
jhammond@nuclear:~/PRK/FORTRAN$ gfortran -fopenmp -c r1.F90 ; gfortran -fopenmp -c r2.F90
r2.F90:22:23:
22 | !$omp& firstprivate(r) &
| 1
Error: Object ‘r’ is not a variable at (1)
Intel
jhammond@nuclear:~/PRK/FORTRAN$ ifort -fopenmp -c r1.F90 ; ifort -fopenmp -c r2.F90
r2.F90(22): error #7655: A variable is required in this OpenMP* context. [2]
!$omp& firstprivate(r) &
---------------------^
r2.F90(21): error #7656: Subobjects are not allowed in this OpenMP* clause; a named variable must be specified.
!$omp parallel default(none) &
^
compilation aborted for r2.F90 (code 1)