Files
clang-p2996/flang/test/Semantics/OpenMP/default-none.f90
harishch4 40fae67a50 [Flang][OpenMP] Fix to construct-names inside OpenMP construct with default(none) (#82479)
When a do loop with a construct-name is used inside OpenMP construct
with default(none), an incorrect error will be raised as below.

```
program cn_and_default
    implicit none
    integer :: i

    !$omp parallel default(none)
        loop: do i = 1, 10
        end do loop
    !$omp end parallel
end program
```

> The DEFAULT(NONE) clause requires that 'loop' must be listed in a
data-sharing attribute clause

This patch fixes this by adding a condition to check and skip processing
construct-names.
2024-02-21 17:44:54 +05:30

50 lines
1.0 KiB
Fortran

!RUN: %python %S/../test_errors.py %s %flang -fopenmp
! Positive tests for default(none)
subroutine sb2(x)
real :: x
end subroutine
subroutine sb1
integer :: i
real :: a(10), b(10), k
inc(x) = x + 1.0
abstract interface
function iface(a, b)
real, intent(in) :: a, b
real :: iface
end function
end interface
procedure(iface) :: compute
procedure(iface), pointer :: ptr => NULL()
ptr => fn2
!$omp parallel default(none) shared(a,b,k) private(i)
do i = 1, 10
b(i) = k + sin(a(i)) + inc(a(i)) + fn1(a(i)) + compute(a(i),k) + add(k, k)
call sb3(b(i))
call sb2(a(i))
end do
!$omp end parallel
contains
function fn1(x)
real :: x, fn1
fn1 = x
end function
function fn2(x, y)
real, intent(in) :: x, y
real :: fn2
fn2 = x + y
end function
subroutine sb3(x)
real :: x
print *, x
end subroutine
end subroutine
!construct-name inside default(none)
subroutine sb4
!$omp parallel default(none)
loop: do i = 1, 10
end do loop
!$omp end parallel
end subroutine