Skip to content

[OpenACC] reduction(+:norm) leads to Error: !$OMP DECLARE REDUCTION plus not found at (1) #1349

Open
@jeffhammond

Description

@jeffhammond

OpenACC seems to be translated to OpenMP but fails to comprehend the build-in + operator in reductions, even though OpenMP does.

jhammond@nuclear:~/PRK/FORTRAN$ /usr/local/bin/flang -g -O3 -fopenacc acc-red.F90
flang_unparsed_file_ca2f7203507f_0.f90:21:42:

   21 | !$ACC PARALLEL LOOP COLLAPSE(2) REDUCTION(PLUS:norm)
      |                                          1
Error: !$OMP DECLARE REDUCTION plus not found at (1)
flang: in /home/jhammond/PRK/FORTRAN, gfortran failed with exit status 1: gfortran -g -O3 -fopenacc -g -O3 -fopenacc acc-red.F90

acc-red.F90

program main
  use iso_fortran_env
  use prk
  implicit none
  integer :: err
  integer(kind=INT32) ::  n,i,j
  real(kind=REAL64), allocatable :: B(:,:)
  real(kind=REAL64) :: norm

  allocate( B(n,n), stat=err)
  if (err .ne. 0) then
    write(*,'(a,i3)') 'allocation of A returned ',err
    stop 1
  endif

  !$acc data pcopy(B)

  !$acc parallel loop collapse(2)
  do j=1,n
    do i=1,n
      B(i,j) = i+j
    enddo
  enddo

  !$acc parallel loop collapse(2) reduction(+:norm)
  do j=1,n
    do i=1,n
      norm = norm + abs(B(i,j))
    enddo
  enddo

  !$acc end data

  deallocate( B )
  print*,norm

end program main

It's fine when OpenMP is used directly:

jhammond@nuclear:~/PRK/FORTRAN$ /usr/local/bin/flang -g -O3 -fopenmp omp-red.F90 && echo OK
OK
jhammond@nuclear:~/PRK/FORTRAN$ cat omp-red.F90
program main
  use iso_fortran_env
  use prk
  implicit none
  integer :: err
  integer(kind=INT32) ::  n,i,j
  real(kind=REAL64), allocatable :: B(:,:)
  real(kind=REAL64) :: norm

  allocate( B(n,n), stat=err)
  if (err .ne. 0) then
    write(*,'(a,i3)') 'allocation of A returned ',err
    stop 1
  endif

  !$omp parallel do collapse(2)
  do j=1,n
    do i=1,n
      B(i,j) = i+j
    enddo
  enddo
  !$omp end parallel do

  !$omp parallel do collapse(2) reduction(+:norm)
  do j=1,n
    do i=1,n
      norm = norm + abs(B(i,j))
    enddo
  enddo
  !$omp end parallel do

  deallocate( B )
  print*,norm

end program main

Metadata

Metadata

Assignees

No one assigned

    Labels

    OpenACCOpenMPLowering and codegen of OpenMPSemanticsIssues, such as unreported language constraint violations, that should be handled in semantics

    Type

    No type

    Projects

    No projects

    Milestone

    No milestone

    Relationships

    None yet

    Development

    No branches or pull requests

    Issue actions