Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.

Bug with do concurrent and openmp

Wolf_W_
New Contributor I
1,870 Views

Hi,

i didn't see this issue in the forums, so i am posting this as information (I opened a support ticket). I got a nasty bug with ifort 19.1 (PSXE 20). The results of do concurrent loops seem to be random, when compiled with /Qopenmp. This happens with independet of the optimization level. Additionally the compiler does not recognize the usage of i as loop counter...

program MAIN
  implicit none

  character(*), parameter :: ALPHABET_UPPER = 'ABCDEFGHIJKLMNOPQRSTUVWXYZÄÖÜß'
  character(*), parameter :: ALPHABET_LOWER = 'abcdefghijklmnopqrstuvwxyzäöüß'
  integer :: j

 ! Gives random results, when compiled with /Qopenmp (with and without optimizations):
  write(*,*)convertToUpperCase("abcdefghijklmnopqrstuvwxyz")
  write(*,*)"ABCDEFGHIJKLMNOPQRSTUVWXYZ"

  do j=1,160
    write(*,'(L1)', advance='no') (convertToUpperCase("abcdefghijklmnopqrstuvwxyzäöüß") == "ABCDEFGHIJKLMNOPQRSTUVWXYZÄÖÜß")
  end do

contains

  pure function convertToUpperCase(str_value) result (new)
    implicit none
    character(len=*), intent(in   ) :: str_value

    character(len(str_value)) :: new
    integer                   :: i   ! Wrong: remark #7712: This variable has not been used.   

    new = str_value
    ! Works with normal do loop
    do concurrent (i = 1:len_trim(str_value))
      block
        integer :: k
        k = index(ALPHABET_LOWER,new(i:i))
        if ( k > 0 ) new(i:i) = ALPHABET_UPPER(k:k)
      end block
    end do

  end function convertToUpperCase

end program

Regards,

Wolf

0 Kudos
5 Replies
Andreas_Z_
New Contributor I
1,870 Views

Hi

I was just going to submit a similar bug report when I saw this thread. I ran into the same problem after installing the latest IVF compiler. 

My simple test case to reproduce this bug is shown below and the code file attached. Note that the issue with 'do concurrent' only surfaces with /Qopenmp when I have involved array variables declared as !$OMP THREADPRIVATE, even though no OpenMP parallel blocks are used in the code. This seems to lead the IVF compiler 19.1.0.166 version to treat only one (here the first) element of array 'bb', while the other elements are left untouched -- possibly because the compiler changes those elements for a different copy of 'bb' in a different thread(?) -- not the expected behavior. No such issue with IVF compiler 19.0.5.28.

Compiler command line:

/nologo /debug:full /Od /Qopenmp /warn:declarations /warn:unused /warn:ignore_loc /warn:truncated_source /warn:uncalled /warn:interfaces /module:"x64\Debug\\" /object:"x64\Debug\\" /Fd"x64\Debug\vc160.pdb" /traceback /check:bounds /libs:static /threads /dbglibs /c

Best,
Andi

module mod1

implicit none
integer(4),dimension(10, 3),public :: aa
integer(4),dimension(3, 10),public :: bb, cc

!$OMP THREADPRIVATE(aa, bb, cc)

contains
    !-------------------------------------
    subroutine dimflip()
    implicit none
    integer(4) :: k, kmax
    !........................
    kmax = size(aa(1,:))
    
    do concurrent ( k = 1:kmax )
        bb(k,:) = aa(:,k)
    enddo

    do k = 1,kmax
        cc(k,:) = aa(:,k)
    enddo
    
    end subroutine dimflip
    !-------------------------------------
end module mod1
    

program TestDoConcurrent

use mod1
implicit none
integer(4) :: i, k

bb = 99
cc = 88
do k = 1,3
    aa(:,k) = [(i, i = 1,10)]
enddo

call dimflip()
write(*,*) "bb(1:3,1): ", bb(1:3,1)
write(*,*) "bb(1:3,2): ", bb(1:3,2)
write(*,*) "cc(1:3,1): ", cc(1:3,1)
write(*,*) "cc(1:3,2): ", cc(1:3,2)
read(*,*)

end program TestDoConcurrent 

 

result with Intel(R) Visual Fortran Compiler 19.1.0.166
 bb(1:3,1):            1          99          99
 bb(1:3,2):            2          99          99
 cc(1:3,1):            1           1           1
 cc(1:3,2):            2           2           2
 
 result with Intel(R) Visual Fortran Compiler 19.0.5.28 (as expected)
 bb(1:3,1):            1           1           1
 bb(1:3,2):            2           2           2
 cc(1:3,1):            1           1           1
 cc(1:3,2):            2           2           2

0 Kudos
IanH
Honored Contributor II
1,870 Views

The current OpenMP specification (5.0) says that use of DO CONCURRENT may result in unspecified behaviour - see https://www.openmp.org/spec-html/5.0/openmpse7.html#x28-270001.7

Given reasonable implementation of DO CONCURRENT, I wouldn't be mixing the two.

The index of a do concurrent construct is a construct local entity.  In the absence of a specification to the contrary, the type of the construct entity can be given by a type declaration statement for an entity with the same name in an enclosing scoping unit, but the index and the thing declared in the enclosing scope are different entities.  The warning about the variable not being used is correct.

Just specify the type of the index in the DO CONCURRENT header, rather than relying on the declaration in the enclosing scoping unit.

do concurrent (integer :: i = 1:len_trim(str_value))

 

 

0 Kudos
Wolf_W_
New Contributor I
1,870 Views

I got an answer from intel support. The block construct is at fault. It can be worked around be using the new (?) local() feature of the do concurrent loop. He also said, that the unused variable warning is a bug and will be patched in 19.1 update 1. It probably is better to use the local definition as you stated, but this warning is misleading, because it suggests to remove the variable, which obviously leads to a compile error.

The do concurrent loop is not executed in a omp parallel region here. Not cobining the two would mean to not use do concurrent at all, when compiling with openmp?

Greetings

Wolf

0 Kudos
Steve_Lionel
Honored Contributor III
1,870 Views

Locality clauses in DO CONCURRENT are new in Fortran 2018.

0 Kudos
ScottBoyce
Beginner
1,853 Views

I have the same problem, but without OpenMP.

This is getting a bit frustrating because everytime I update to the newest Intel I have to spend a week refactoring code because something no long works.

 

Here is an example program that does not use OpenMP that crashes:. I also compile it with the/assume:nocc_omp flag to remove the dependence on the OpenMP dll.

 

! This was not a problem with Intel(R) Visual Fortran Compiler 18.0.5.274 [Intel(R) 64] (Sets B=1)
!      This error occurs with version 19.1.1.216 and 19.1.2.254
!
! This error occurs if you enable any one of the following Run-time Checks
! /check:uninit
! /check:bounds
! /check:stack
!
! Error seems to occur whenever there is two DO CONCURRENT loops and an ASSOCIATE construct.
! 
! Also sometimes I get eratic behavior with multiple DO CONCCURENTS in a row.
!
! Note this compilation also raises the warning 
!    "Message		remark #7712: This variable has not been used.   [I]		Main.f90	27	"
!    "Message		remark #7712: This variable has not been used.   [J]		Main.f90	28	"
!
PROGRAM MAIN
  IMPLICIT NONE
  INTEGER, PARAMETER:: D1=5, D2=10
  INTEGER, DIMENSION(D1,D2):: A,B
  INTEGER:: I, J
  !
  A = 1
  !
  !First iteration has I=J=-858993460
  ! cmd prompt says: Run-Time Check Failure. The variable \'MAIN$J\' is being used in \'Main.f90(68,24)\' without being defined
  DO CONCURRENT ( I = 1:D1 )
  DO CONCURRENT ( J = 1:D2 ) 
      ASSOCIATE( P1 => A(I,J) ) 
         B(I,J) = P1
      END ASSOCIATE
  END DO
  END DO
  
  PAUSE
END PROGRAM

 

 

0 Kudos
Reply