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

Uninitialized or undefined variable in Visual Studio debugger using Fortran and OpenMP

RyanKruk
Beginner
1,716 Views

I'm having an issue with the debugger output in Visual Studio, which is showing uninitialized or in some cases undefined variables upon entering an OpenMP parallel section. This occurs despite declaring the variables as firstprivate. I've tested a couple scenarios and the issue occurs for subroutine arguments. I've put together a MWE to demonstrate that this problem does not appear for local variables or common variables, but it does exist for non-common and common variables alike that are passed in as arguments to a subroutine. This can be seen in Fig. 1 where execution can be seen paused at L43 by a breakpoint in the OMP parallel do section. The tested variables are as follows:

  • arg1: test_arg passed in from main to feeder and subsequently into test_subroutine. (Problem)
  • test_loc:  local variable created in test_subroutine. (Good)
  • test_glob1: common variable created in main and accessed in test_subroutine. (Good)
  • arg2: test_glob2 defined in MWEh.for, initialized in init, and passed into test_subroutine from feeder. (Problem)

Fig. 1:

RyanKruk_0-1651621470295.png


This MWE is as close of a program to the project I’m working on where I get similar behaviour, but variables in this other project actually become undefined in the debugger as opposed to garbage data. When I reduce the size of an array that appears as undefined from ~3k elements to 3 in this other project for example, the variable is shown as garbage data instead of undefined. This somewhat leads me to believe that the VS debugger is limited in memory, but this is only speculation. I could not "break" the MWE in such a way to show undefined variables however. The only apparent difference between the other project and the MWE shown here is the number of input arguments to any subroutine. The other project easily has 50+ input arguments to any given subroutine, which is part of the reason I thought a MWE was necessary to post here. Could this be a contributing factor for why variables are shown as undefined? I'll re-iterate that in this other project, I also use a parallel do loop and label the required variables as firstprivate as I did in the MWE.


Despite Visual Studio showing garbage data in the debugger, the values are printed correctly as shown in Fig. 2. I ran the program with 1 thread, but the problem occurs for any number of threads Is this something I should be concerned about? Even if it's not a concern, I'd appreciate any insight into why the debugger is behaving in this manner.

Fig. 2:

RyanKruk_1-1651622050596.png


I'm using Visual Studio 2022 with Intel Fortran Compiler Classic 2021.5.0, although I first encountered this problem in Visual Studio 2012 with Intel Visual Fortran Compiler XE 14.0.2.176. I have /debug-parameters:used and /Qopenmp compiler flags activated.

 

Thank you in advance for any and all help provided.

 

MWE.for:

 

      subroutine test_subroutine(arg1, arg2)
          common /test_block/ test_glob1
          character(20) :: fmt1, fmt2
          real(4),intent(in)::arg1(3), arg2(100000)
          real(4)::test_glob1(3)
          real(4)::test_loc(3)

          test_loc = (/4, 5, 6/)
          fmt1 = "(A31,I8)"
          print fmt1, 'Address of arg1              = ', loc(arg1)
          print fmt1, 'Address of test_loc          = ', loc(test_loc)
          print fmt1, 'Address of test_glob1        = ', loc(test_glob1)
          print fmt1, 'Address of test_glob2 (arg2) = ', loc(arg2)
          print *, 'Entering do loop...'
!$OMP PARALLEL DO FIRSTPRIVATE(arg1, test_loc, test_glob1, arg2)
          do i = 1, 3
              print '( A5,I1,A17,F3.1,A12,I8)', 'arg1(', i, ')              = ', arg1(i),       '. Address = ', loc(arg1(i))
              print '( A9,I1,A13,F3.1,A12,I8)', 'test_loc(', i, ')          = ', test_loc(i),   '. Address = ', loc(test_loc(i))
              print '(A11,I1,A11,F3.1,A12,I8)', 'test_glob1(', i, ')        = ', test_glob1(i), '. Address = ', loc(test_glob1(i))
              print '(A11,I1,A11,F3.1,A12,I8)', 'test_glob2(', i, ') (arg2) = ', arg2(i),       '. Address = ', loc(arg2(i))
          end do
!$OMP END PARALLEL DO
          return
      end

      subroutine feeder(test_arg)
          include 'MWEh.for'
          real(4),intent(in)::test_arg(3)
          call test_subroutine(test_arg, test_glob2)
      end

      subroutine init
          include 'MWEh.for'
          do i = 1, n
              test_glob2(i) = i
          end do
      end

      program MWE

          use omp_lib

          ! Variables
          common /test_block/ test_glob1
          real(4) :: test_glob1(3)
          real(4) :: test_arg(3)
          character(1) :: nthreads_string
          integer :: rank, nthreads
          
          call init
          test_arg = (/1, 2, 3/)
          test_glob1 = (/7, 8, 9/)

          ! Body of MWE
!DEC$ IF DEFINED (_OPENMP)
              call get_command_argument(1,nthreads_string)
              read (nthreads_string,*) nthreads
              call OMP_SET_NUM_THREADS(nthreads)
              print *, 'Running MWE in Parallel on', nthreads, 'threads'
!$OMP PARALLEL PRIVATE(rank)
              rank = OMP_GET_THREAD_NUM()
!$OMP END PARALLEL
!DEC$ ELSE
              pause 'This MWE must be run in parallel. Enable OpenMP'
              call exit(0)
!DEC$ ENDIF
!$OMP BARRIER

          call feeder(test_arg)
      end program MWE

 

MWEh.for:

 

!     Header file
      parameter(n=100000)
      common /extern_block/ test_glob2(n)

 

 

Labels (4)
0 Kudos
6 Replies
jimdempseyatthecove
Honored Contributor III
1,669 Views

A work around:

      subroutine test_subroutine(arg1, arg2)
          common /test_block/ test_glob1
          character(20) :: fmt1, fmt2
          real(4),intent(in)::arg1(3), arg2(100000)
          real(4)::test_glob1(3)
          real(4)::test_loc(3)

          test_loc = (/4, 5, 6/)
          fmt1 = "(A31,I8)"
          print fmt1, 'Address of arg1              = ', loc(arg1)
          print fmt1, 'Address of test_loc          = ', loc(test_loc)
          print fmt1, 'Address of test_glob1        = ', loc(test_glob1)
          print fmt1, 'Address of test_glob2 (arg2) = ', loc(arg2)
          print *, 'Entering do loop...'
!$OMP PARALLEL FIRSTPRIVATE(arg1, test_loc, test_glob1, arg2)
          call foo(arg1, test_loc, test_glob1, arg2)
!$OMP END PARALLEL
          return
      end


      subroutine foo(arg1, test_loc, test_glob1, arg2)
          implicit none
          real(4),intent(in)::arg1(:), arg2(:)
          real(4)::test_glob1(:)
          real(4)::test_loc(:)
          integer :: i
          do i = 1, 3
              print '( A5,I1,A17,F3.1,A12,I8)', 'arg1(', i, ')              = ', arg1(i),       '. Address = ', loc(arg1(i))
              print '( A9,I1,A13,F3.1,A12,I8)', 'test_loc(', i, ')          = ', test_loc(i),   '. Address = ', loc(test_loc(i))
              print '(A11,I1,A11,F3.1,A12,I8)', 'test_glob1(', i, ')        = ', test_glob1(i), '. Address = ', loc(test_glob1(i))
              print '(A11,I1,A11,F3.1,A12,I8)', 'test_glob2(', i, ') (arg2) = ', arg2(i),       '. Address = ', loc(arg2(i))
          end do
      end subroutine foo

You can also make that a contained procedure, and then not pass shared objects via call dummies.

Jim Dempsey

0 Kudos
RyanKruk
Beginner
1,550 Views

Thanks for the workaround @jimdempseyatthecove, I appreaciate it! While it does resolve the VS2022 debugger issue, it would be great if you could explain the rational as to why it works or why VS doesn't show the correct variable values in the debugger.

I took some time to test this workaround and there is one outstanding issue I'm having. See an updated foo subroutine below. The difference compared to your suggestion is the intent of the arguments to inout and I manipulate values in the array by incrementing them by 1. The end goal is to update the array in the calling routine (test_subroutine) with the calculated values performed privately to each thread. I'm not sure if I should make this a new post or not since the goal is different, but I'll leave it here for the time being.

A couple caveats: I needed to re-introduce the use omp_lib command at the top of the foo subroutine to make rank work properly. As a side question, do I need to invoke use omp_lib in all subroutines that use parallelization? This seems odd to me since it is already invoked in the main program and in this MWE case, all subroutines are defined in the same file. Rank would print out as -2147483648 or NaN without it and I'm wondering if there are other things that wouldn't work as expected without re-introducing use omp_lib.

 

      subroutine foo(arg1, test_loc, test_glob1, arg2)
          use omp_lib
          implicit none
          real(4),intent(inout)::arg1(3), arg2(100000), test_glob1(3), test_loc(3)
          integer :: i, rank

          rank =  OMP_GET_THREAD_NUM()
          call sleep(2*rank)
          print *, 'Inside foo...'
          !$OMP DO
          do i = 1, 3
              print *, 'Rank: ', rank
              arg1(i) = arg1(i) + 1
              test_loc(i) = test_loc(i) + 1
              test_glob1(i) = test_glob1(i) + 1
              arg2(i) = arg2(i) + 1

              print '( A5,I1,A17,F3.1,A12,I8)', 'arg1(', i, ')              = ', arg1(i),       '. Address = ', loc(arg1(i))
              print '( A9,I1,A13,F3.1,A12,I8)', 'test_loc(', i, ')          = ', test_loc(i),   '. Address = ', loc(test_loc(i))
              print '(A11,I1,A11,F3.1,A12,I8)', 'test_glob1(', i, ')        = ', test_glob1(i), '. Address = ', loc(test_glob1(i))
              print '(A11,I1,A11,F3.1,A12,I8)', 'test_glob2(', i, ') (arg2) = ', arg2(i),       '. Address = ', loc(arg2(i))
          end do
          !$OMP END DO

 

In an attempt to update the arrays in the calling subroutine, I've tried the following with no success (see comments). Error #6761 doesn't make sense to me since I'm doing exactly what it states in the exception clause.

      subroutine test_subroutine(arg1, arg2)
          use omp_lib
          common /test_block/ test_glob1
          integer::rank
          character(20) :: fmt1, fmt2
          real(4),intent(inout)::arg1(3), arg2(100000)
          real(4)::test_glob1(3)
          real(4)::test_loc(3)

          test_loc = (/4, 5, 6/)
          fmt1 = "(A31,I8)"
          print fmt1, 'Address of arg1              = ', loc(arg1)
          print fmt1, 'Address of test_loc          = ', loc(test_loc)
          print fmt1, 'Address of test_glob1        = ', loc(test_glob1)
          print fmt1, 'Address of test_glob2 (arg2) = ', loc(arg2)
          print *, 'Entering do loop...'
          ! This compiles, but does not update the entire array,
          ! however this is the expected behaviour of LASTPRIVATE.
          !$OMP PARALLEL DO FIRSTPRIVATE(arg1, test_loc, test_glob1, arg2) LASTPRIVATE(arg1, test_loc, test_glob1, arg2)
          do i = 1, 3
              test_loc(i) = test_loc(i) + 1
              print '( A5,I1,A17,F3.1,A12,I8)', 'arg1(', i, ')              = ', arg1(i),       '. Address = ', loc(arg1(i))
              print '( A9,I1,A13,F3.1,A12,I8)', 'test_loc(', i, ')          = ', test_loc(i),   '. Address = ', loc(test_loc(i))
              print '(A11,I1,A11,F3.1,A12,I8)', 'test_glob1(', i, ')        = ', test_glob1(i), '. Address = ', loc(test_glob1(i))
              print '(A11,I1,A11,F3.1,A12,I8)', 'test_glob2(', i, ') (arg2) = ', arg2(i),       '. Address = ', loc(arg2(i))
          end do
          !$OMP END PARALLEL DO

          ! This does not compile.
          ! Error #6761: An entity cannot appear explicitly in more than one
          ! clause per directive except that an entity can be specified in both
          ! a FIRSTPRIVATE and LASTPRIVATE clause.
          !$OMP PARALLEL FIRSTPRIVATE(arg1, test_loc, test_glob1, arg2) LASTPRIVATE(arg1, test_loc, test_glob1, arg2)
          !$OMP DO
          do i = 1, 3
              test_loc(i) = test_loc(i) + 1
              print '( A5,I1,A17,F3.1,A12,I8)', 'arg1(', i, ')              = ', arg1(i),       '. Address = ', loc(arg1(i))
              print '( A9,I1,A13,F3.1,A12,I8)', 'test_loc(', i, ')          = ', test_loc(i),   '. Address = ', loc(test_loc(i))
              print '(A11,I1,A11,F3.1,A12,I8)', 'test_glob1(', i, ')        = ', test_glob1(i), '. Address = ', loc(test_glob1(i))
              print '(A11,I1,A11,F3.1,A12,I8)', 'test_glob2(', i, ') (arg2) = ', arg2(i),       '. Address = ', loc(arg2(i))
          end do
          !$OMP END DO
          !$OMP END PARALLEL

          ! This does not compile. Same error as above.
          !$OMP PARALLEL FIRSTPRIVATE(arg1, test_loc, test_glob1, arg2) LASTPRIVATE(arg1, test_loc, test_glob1, arg2)
          call foo(arg1, test_loc, test_glob1, arg2)
          !$OMP END PARALLEL
          print *, 'Out of parallel loop...'
          print *, 'Check updated variable.'
          do i = 1, 3
              print '( A9,I1,A13,F3.1,A12,I8)', 'test_loc(', i, ')          = ', test_loc(i),   '. Address = ', loc(test_loc(i))
          end do
          return
      end

 Once again, I appreciate any help on this and thank you in advance!

0 Kudos
RyanKruk
Beginner
1,550 Views

Thanks for the workaround @jimdempseyatthecove, I appreaciate it! While it does resolve the VS2022 debugger issue, it would be great if you could explain the rational as to why it works or why VS doesn't show the correct variable values in the debugger.

I took some time to test this workaround and there is one outstanding issue I'm having. The end goal is to update the entire array in the calling routine (test_subroutine) based on the work done privately to each thread in the foo subroutine. See updated versions of these subroutines below. The difference compared to your suggestion is the intent of the arguments to inout and I manipulate values in the array by incrementing them by 1 (just some placeholder work for the MWE). Also note that I needed to re-introduce the "use omp_lib" command at the top of the subroutine to make rank work properly.

As a side question, do I need to invoke "use omp_lib" in all subroutines for the proper functionality of omp? This seems odd to me since it is already invoked in the main program and in this MWE case, all subroutines are defined in the same file. Rank would print out as -2147483648 or NaN without it and I'm wondering if there are other things that wouldn't work as expected without.

I've inserted itemized attempts in test_subroutine at updating test_loc with the work done privately to each thread. I unfortunately get the wrong result with attempt 1, although expected, but I get compile errors (see comments) with attempts 2 and 3 despite doing what the error says it should allow.

I'm quite new to OpenMP so I don't know what other approaches could be taken to perform this task, but I would like to note that I do not want to make test_loc a shared variable to do this. Thank you in advance for any suggestions you may have.

      subroutine test_subroutine(arg1, arg2)
          use omp_lib
          common /test_block/ test_glob1
          integer::rank
          character(20) :: fmt1, fmt2
          real(4),intent(inout)::arg1(3), arg2(100000)
          real(4)::test_glob1(3)
          real(4)::test_loc(3)

          test_loc = (/4, 5, 6/)
          fmt1 = "(A31,I8)"
          print fmt1, 'Address of arg1              = ', loc(arg1)
          print fmt1, 'Address of test_loc          = ', loc(test_loc)
          print fmt1, 'Address of test_glob1        = ', loc(test_glob1)
          print fmt1, 'Address of test_glob2 (arg2) = ', loc(arg2)
          print *, 'Entering do loop...'
          ! Attempt 1:
          ! This compiles, but does not update the entire array,
          ! however this is the expected behaviour of LASTPRIVATE.
          !$OMP PARALLEL DO FIRSTPRIVATE(arg1, test_loc, test_glob1, arg2) LASTPRIVATE(arg1, test_loc, test_glob1, arg2)
          do i = 1, 3
              test_loc(i) = test_loc(i) + 1
              print '( A5,I1,A17,F3.1,A12,I8)', 'arg1(', i, ')              = ', arg1(i),       '. Address = ', loc(arg1(i))
              print '( A9,I1,A13,F3.1,A12,I8)', 'test_loc(', i, ')          = ', test_loc(i),   '. Address = ', loc(test_loc(i))
              print '(A11,I1,A11,F3.1,A12,I8)', 'test_glob1(', i, ')        = ', test_glob1(i), '. Address = ', loc(test_glob1(i))
              print '(A11,I1,A11,F3.1,A12,I8)', 'test_glob2(', i, ') (arg2) = ', arg2(i),       '. Address = ', loc(arg2(i))
          end do
          !$OMP END PARALLEL DO

          ! Attempt 2:
          ! This does not compile.
          ! Error #6761: An entity cannot appear explicitly in more than one
          ! clause per directive except that an entity can be specified in both
          ! a FIRSTPRIVATE and LASTPRIVATE clause.
          !$OMP PARALLEL FIRSTPRIVATE(arg1, test_loc, test_glob1, arg2)! LASTPRIVATE(arg1, test_loc, test_glob1, arg2)
          !$OMP DO
          do i = 1, 3
              test_loc(i) = test_loc(i) + 1
              print '( A5,I1,A17,F3.1,A12,I8)', 'arg1(', i, ')              = ', arg1(i),       '. Address = ', loc(arg1(i))
              print '( A9,I1,A13,F3.1,A12,I8)', 'test_loc(', i, ')          = ', test_loc(i),   '. Address = ', loc(test_loc(i))
              print '(A11,I1,A11,F3.1,A12,I8)', 'test_glob1(', i, ')        = ', test_glob1(i), '. Address = ', loc(test_glob1(i))
              print '(A11,I1,A11,F3.1,A12,I8)', 'test_glob2(', i, ') (arg2) = ', arg2(i),       '. Address = ', loc(arg2(i))
          end do
          !$OMP END DO
          !$OMP END PARALLEL

          ! Attempt 3:
          ! This does not compile. Same error as above.
          !$OMP PARALLEL FIRSTPRIVATE(arg1, test_loc, test_glob1, arg2)! LASTPRIVATE(arg1, test_loc, test_glob1, arg2)
          call foo(arg1, test_loc, test_glob1, arg2)
          !$OMP END PARALLEL
          print *, 'Out of parallel loop...'
          print *, 'Check updated variable.'
          do i = 1, 3
              print '( A9,I1,A13,F3.1,A12,I8)', 'test_loc(', i, ')          = ', test_loc(i),   '. Address = ', loc(test_loc(i))
          end do
          return
      end
      subroutine foo(arg1, test_loc, test_glob1, arg2)
          use omp_lib
          implicit none
          real(4),intent(inout)::arg1(3), arg2(100000), test_glob1(3), test_loc(3)
          integer::i, rank
          integer::schedule_kind,chunk_size

          rank = OMP_GET_THREAD_NUM()
          call OMP_GET_SCHEDULE(schedule_kind,chunk_size)
          call sleep(2*rank)
          print *, 'Inside foo...'
          !$OMP DO
          do i = 1, 3
              print *, 'Rank: ', rank
              arg1(i) = arg1(i) + 1
              test_loc(i) = test_loc(i) + 1
              test_glob1(i) = test_glob1(i) + 1
              arg2(i) = arg2(i) + 1

              print '( A5,I1,A17,F3.1,A12,I8)', 'arg1(', i, ')              = ', arg1(i),       '. Address = ', loc(arg1(i))
              print '( A9,I1,A13,F3.1,A12,I8)', 'test_loc(', i, ')          = ', test_loc(i),   '. Address = ', loc(test_loc(i))
              print '(A11,I1,A11,F3.1,A12,I8)', 'test_glob1(', i, ')        = ', test_glob1(i), '. Address = ', loc(test_glob1(i))
              print '(A11,I1,A11,F3.1,A12,I8)', 'test_glob2(', i, ') (arg2) = ', arg2(i),       '. Address = ', loc(arg2(i))
          end do
          !$OMP END DO
      end subroutine foo

 

0 Kudos
RyanKruk
Beginner
1,550 Views

Thanks for the workaround @jimdempseyatthecove , I appreaciate it! While it does resolve the VS2022 debugger issue, it would be great if you could explain the rational as to why it works or why VS doesn't show the correct variable values in the debugger.

I took some time to test this workaround and there is one outstanding issue I'm having. The end goal is to update the entire array in the calling routine (test_subroutine) based on the work done privately to each thread in the foo subroutine. See updated versions of these subroutines below. The difference compared to your suggestion is the intent of the arguments to inout and I manipulate values in the array by incrementing them by 1 (just some placeholder work for the MWE). Also note that I needed to re-introduce the "use omp_lib" command at the top of the subroutine to make rank work properly.

As a side question, do I need to invoke "use omp_lib" in all subroutines for the proper functionality of omp? This seems odd to me since it is already invoked in the main program and in this MWE case, all subroutines are defined in the same file. Rank would print out as -2147483648 or NaN without it and I'm wondering if there are other things that wouldn't work as expected without.

I've inserted itemized attempts in test_subroutine at updating test_loc with the work done privately to each thread. I unfortunately get the wrong result with attempt 1, although expected, but I get compile errors (see comments) with attempts 2 and 3 despite doing what the error says it should allow.

I'm quite new to OpenMP so I don't know what other approaches could be taken to perform this task, but I would like to note that I do not want to make test_loc a shared variable to do this. Thank you in advance for any suggestions you may have.

      subroutine test_subroutine(arg1, arg2)
          use omp_lib
          common /test_block/ test_glob1
          integer::rank
          character(20) :: fmt1, fmt2
          real(4),intent(inout)::arg1(3), arg2(100000)
          real(4)::test_glob1(3)
          real(4)::test_loc(3)

          test_loc = (/4, 5, 6/)
          fmt1 = "(A31,I8)"
          print fmt1, 'Address of arg1              = ', loc(arg1)
          print fmt1, 'Address of test_loc          = ', loc(test_loc)
          print fmt1, 'Address of test_glob1        = ', loc(test_glob1)
          print fmt1, 'Address of test_glob2 (arg2) = ', loc(arg2)
          print *, 'Entering do loop...'
          ! Attempt 1:
          ! This compiles, but does not update the entire array,
          ! however this is the expected behaviour of LASTPRIVATE.
          !$OMP PARALLEL DO FIRSTPRIVATE(arg1, test_loc, test_glob1, arg2) LASTPRIVATE(arg1, test_loc, test_glob1, arg2)
          do i = 1, 3
              test_loc(i) = test_loc(i) + 1
              print '( A5,I1,A17,F3.1,A12,I8)', 'arg1(', i, ')              = ', arg1(i),       '. Address = ', loc(arg1(i))
              print '( A9,I1,A13,F3.1,A12,I8)', 'test_loc(', i, ')          = ', test_loc(i),   '. Address = ', loc(test_loc(i))
              print '(A11,I1,A11,F3.1,A12,I8)', 'test_glob1(', i, ')        = ', test_glob1(i), '. Address = ', loc(test_glob1(i))
              print '(A11,I1,A11,F3.1,A12,I8)', 'test_glob2(', i, ') (arg2) = ', arg2(i),       '. Address = ', loc(arg2(i))
          end do
          !$OMP END PARALLEL DO

          ! Attempt 2:
          ! This does not compile.
          ! Error #6761: An entity cannot appear explicitly in more than one
          ! clause per directive except that an entity can be specified in both
          ! a FIRSTPRIVATE and LASTPRIVATE clause.
          !$OMP PARALLEL FIRSTPRIVATE(arg1, test_loc, test_glob1, arg2)! LASTPRIVATE(arg1, test_loc, test_glob1, arg2)
          !$OMP DO
          do i = 1, 3
              test_loc(i) = test_loc(i) + 1
              print '( A5,I1,A17,F3.1,A12,I8)', 'arg1(', i, ')              = ', arg1(i),       '. Address = ', loc(arg1(i))
              print '( A9,I1,A13,F3.1,A12,I8)', 'test_loc(', i, ')          = ', test_loc(i),   '. Address = ', loc(test_loc(i))
              print '(A11,I1,A11,F3.1,A12,I8)', 'test_glob1(', i, ')        = ', test_glob1(i), '. Address = ', loc(test_glob1(i))
              print '(A11,I1,A11,F3.1,A12,I8)', 'test_glob2(', i, ') (arg2) = ', arg2(i),       '. Address = ', loc(arg2(i))
          end do
          !$OMP END DO
          !$OMP END PARALLEL

          ! Attempt 3:
          ! This does not compile. Same error as above.
          !$OMP PARALLEL FIRSTPRIVATE(arg1, test_loc, test_glob1, arg2)! LASTPRIVATE(arg1, test_loc, test_glob1, arg2)
          call foo(arg1, test_loc, test_glob1, arg2)
          !$OMP END PARALLEL
          print *, 'Out of parallel loop...'
          print *, 'Check updated variable.'
          do i = 1, 3
              print '( A9,I1,A13,F3.1,A12,I8)', 'test_loc(', i, ')          = ', test_loc(i),   '. Address = ', loc(test_loc(i))
          end do
          return
      end

 

      subroutine foo(arg1, test_loc, test_glob1, arg2)
          use omp_lib
          implicit none
          real(4),intent(inout)::arg1(3), arg2(100000), test_glob1(3), test_loc(3)
          integer::i, rank
          integer::schedule_kind,chunk_size

          rank = OMP_GET_THREAD_NUM()
          call OMP_GET_SCHEDULE(schedule_kind,chunk_size)
          call sleep(2*rank)
          print *, 'Inside foo...'
          !$OMP DO
          do i = 1, 3
              print *, 'Rank: ', rank
              arg1(i) = arg1(i) + 1
              test_loc(i) = test_loc(i) + 1
              test_glob1(i) = test_glob1(i) + 1
              arg2(i) = arg2(i) + 1

              print '( A5,I1,A17,F3.1,A12,I8)', 'arg1(', i, ')              = ', arg1(i),       '. Address = ', loc(arg1(i))
              print '( A9,I1,A13,F3.1,A12,I8)', 'test_loc(', i, ')          = ', test_loc(i),   '. Address = ', loc(test_loc(i))
              print '(A11,I1,A11,F3.1,A12,I8)', 'test_glob1(', i, ')        = ', test_glob1(i), '. Address = ', loc(test_glob1(i))
              print '(A11,I1,A11,F3.1,A12,I8)', 'test_glob2(', i, ') (arg2) = ', arg2(i),       '. Address = ', loc(arg2(i))
          end do
          !$OMP END DO
      end subroutine foo

 

0 Kudos
RyanKruk
Beginner
1,550 Views

Thanks for the workaround @jimdempseyatthecove , I appreaciate it! While it does resolve the VS2022 debugger issue, it would be great if you could explain the rational as to why it works or why VS doesn't show the correct variable values in the debugger.

I took some time to test this workaround and there is one outstanding issue I'm having. The end goal is to update the entire array in the calling routine (test_subroutine) based on the work done privately to each thread in the foo subroutine. See updated versions of these subroutines below. The difference compared to your suggestion is the intent of the arguments to inout and I manipulate values in the array by incrementing them by 1 (just some placeholder work for the MWE). Also note that I needed to re-introduce the "use omp_lib" command at the top of the subroutine to make rank work properly.

As a side question, do I need to invoke "use omp_lib" in all subroutines for the proper functionality of omp? This seems odd to me since it is already invoked in the main program and in this MWE case, all subroutines are defined in the same file. Rank would print out as -2147483648 or NaN without it and I'm wondering if there are other things that wouldn't work as expected without.

I've inserted itemized attempts in test_subroutine at updating test_loc with the work done privately to each thread. I unfortunately get the wrong result with attempt 1, although expected, but I get compile errors (see comments) with attempts 2 and 3 despite doing what the error says it should allow.

I'm quite new to OpenMP so I don't know what other approaches could be taken to perform this task, but I would like to note that I do not want to make test_loc a shared variable to do this. Thank you in advance for any suggestions you may have.

 

 

      subroutine test_subroutine(arg1, arg2)
          use omp_lib
          common /test_block/ test_glob1
          integer::rank
          character(20) :: fmt1, fmt2
          real(4),intent(inout)::arg1(3), arg2(100000)
          real(4)::test_glob1(3)
          real(4)::test_loc(3)

          test_loc = (/4, 5, 6/)
          fmt1 = "(A31,I8)"
          print fmt1, 'Address of arg1              = ', loc(arg1)
          print fmt1, 'Address of test_loc          = ', loc(test_loc)
          print fmt1, 'Address of test_glob1        = ', loc(test_glob1)
          print fmt1, 'Address of test_glob2 (arg2) = ', loc(arg2)
          print *, 'Entering do loop...'
          ! Attempt 1:
          ! This compiles, but does not update the entire array,
          ! however this is the expected behaviour of LASTPRIVATE.
          !$OMP PARALLEL DO FIRSTPRIVATE(arg1, test_loc, test_glob1, arg2) LASTPRIVATE(arg1, test_loc, test_glob1, arg2)
          do i = 1, 3
              test_loc(i) = test_loc(i) + 1
              print '( A5,I1,A17,F3.1,A12,I8)', 'arg1(', i, ')              = ', arg1(i),       '. Address = ', loc(arg1(i))
              print '( A9,I1,A13,F3.1,A12,I8)', 'test_loc(', i, ')          = ', test_loc(i),   '. Address = ', loc(test_loc(i))
              print '(A11,I1,A11,F3.1,A12,I8)', 'test_glob1(', i, ')        = ', test_glob1(i), '. Address = ', loc(test_glob1(i))
              print '(A11,I1,A11,F3.1,A12,I8)', 'test_glob2(', i, ') (arg2) = ', arg2(i),       '. Address = ', loc(arg2(i))
          end do
          !$OMP END PARALLEL DO

          ! Attempt 2:
          ! This does not compile.
          ! Error #6761: An entity cannot appear explicitly in more than one
          ! clause per directive except that an entity can be specified in both
          ! a FIRSTPRIVATE and LASTPRIVATE clause.
          !$OMP PARALLEL FIRSTPRIVATE(arg1, test_loc, test_glob1, arg2)! LASTPRIVATE(arg1, test_loc, test_glob1, arg2)
          !$OMP DO
          do i = 1, 3
              test_loc(i) = test_loc(i) + 1
              print '( A5,I1,A17,F3.1,A12,I8)', 'arg1(', i, ')              = ', arg1(i),       '. Address = ', loc(arg1(i))
              print '( A9,I1,A13,F3.1,A12,I8)', 'test_loc(', i, ')          = ', test_loc(i),   '. Address = ', loc(test_loc(i))
              print '(A11,I1,A11,F3.1,A12,I8)', 'test_glob1(', i, ')        = ', test_glob1(i), '. Address = ', loc(test_glob1(i))
              print '(A11,I1,A11,F3.1,A12,I8)', 'test_glob2(', i, ') (arg2) = ', arg2(i),       '. Address = ', loc(arg2(i))
          end do
          !$OMP END DO
          !$OMP END PARALLEL

          ! Attempt 3:
          ! This does not compile. Same error as above.
          !$OMP PARALLEL FIRSTPRIVATE(arg1, test_loc, test_glob1, arg2)! LASTPRIVATE(arg1, test_loc, test_glob1, arg2)
          call foo(arg1, test_loc, test_glob1, arg2)
          !$OMP END PARALLEL
          print *, 'Out of parallel loop...'
          print *, 'Check updated variable.'
          do i = 1, 3
              print '( A9,I1,A13,F3.1,A12,I8)', 'test_loc(', i, ')          = ', test_loc(i),   '. Address = ', loc(test_loc(i))
          end do
          return
      end
      subroutine foo(arg1, test_loc, test_glob1, arg2)
          use omp_lib
          implicit none
          real(4),intent(inout)::arg1(3), arg2(100000), test_glob1(3), test_loc(3)
          integer::i, rank
          integer::schedule_kind,chunk_size

          rank = OMP_GET_THREAD_NUM()
          call OMP_GET_SCHEDULE(schedule_kind,chunk_size)
          call sleep(2*rank)
          print *, 'Inside foo...'
          !$OMP DO
          do i = 1, 3
              print *, 'Rank: ', rank
              arg1(i) = arg1(i) + 1
              test_loc(i) = test_loc(i) + 1
              test_glob1(i) = test_glob1(i) + 1
              arg2(i) = arg2(i) + 1

              print '( A5,I1,A17,F3.1,A12,I8)', 'arg1(', i, ')              = ', arg1(i),       '. Address = ', loc(arg1(i))
              print '( A9,I1,A13,F3.1,A12,I8)', 'test_loc(', i, ')          = ', test_loc(i),   '. Address = ', loc(test_loc(i))
              print '(A11,I1,A11,F3.1,A12,I8)', 'test_glob1(', i, ')        = ', test_glob1(i), '. Address = ', loc(test_glob1(i))
              print '(A11,I1,A11,F3.1,A12,I8)', 'test_glob2(', i, ') (arg2) = ', arg2(i),       '. Address = ', loc(arg2(i))
          end do
          !$OMP END DO
      end subroutine foo

 

 

 

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,547 Views

I replied to your private message containing the same post.

Jim Dempsey

0 Kudos
Reply