problem with !$acc declare create()

Hello,
I have some Fortran code where some general parameters are defined in one module, and then in used in a separate module that initializes the data values.

module genParamsMod

real(kind=8) :: pi, twoPi, pid2, degs, rad, logten, fp0, c, earthr, plat, plon
parameter( pi=3.1415926535897932384626433d0, & ! pi
    twoPi = 6.283185307179586476925287d0, &    ! 2 pi
    pid2 = 1.570796326794896619231322d0, &     ! pi/2
    rad = 0.01745329251994329576923691d0, &    ! pi/180
    degs = 57.29577951308232087679815d0, &     ! 180/pi
    logten = 2.302585092994045684017991d0, &   ! ln(10)
    c = 2.997925d5, &                          ! speed of light in vacuum, km/s
    earthr = 6371.0990d0, &                    ! earth radius, km
    plat = 1.37183d0, &                        ! magnetic pole latitude
    plon = -1.21824d0 )                        ! magnetic pole longitude
end module genParamsMod

When i compile the code I am getting the error

Module variables used in acc routine need to be in !$acc declare create()

This seems simple enough to fix with an added directive:

module propMod
use genParamsMod
implicit none
contains 
subroutine initArray(var1,var2,var3)
real(kind=8), dimension(:), intent(inout) :: var1, var2, var3
!$acc declare create(pi, twopi)
var1 = 0.0d0
var2 = pi
var3 = twopi

end subroutine 

end module

I get the error

PGF90-S-0000-Internal compiler error. memsym_of_ast:unexp.ast 0

In this case I think I’ll have the simple workaround of adding the variables pi and twopi (etc) locally, but my worry is that either 1. this latter error is a bug, and this is the first of a chain of locations where it will pop up as I add the local variable workaround (defeating the point of having module variables) or – and much more likely – 2. I’ve done something else wrong, but can’t yet figure that out based on the current information from the compiler. Perhaps it has something to do with the scalars being parameters?

Hi sdl,

Thanks for the report. I added TPR#24917 and sent it to engineering for further investigations. The problem being that parameters don’t need to be put into a declare create statement and the compiler should be issuing an error or warning. Looks like our engineers missed this case.

Module variables used in acc routine need to be in !$acc declare create()

For this error, my assumption is that it’s a different variable(s) that the compiler is complaining about. Are there any other module variables being used in the device subroutine?

Also since the scope of the declare directive is the same as the scoping unit where it was used, you’ll want to add it to the module data declaration section where the variable is declared. Not within a subroutine.

-Mat

Hi Mat,
Thanks for the response. I’ve combed through to find what variable(s) the compiler might be complaining about, and managed to find what is probably the culprit (and is a little embarrassing). Hopefully I can illustrate clearly by expanding the code sample I posted previously:

 module genParamsMod 

real(kind=8) :: pi, twoPi, pid2, degs, rad, logten, fp0, c, earthr, plat, plon 
parameter( pi=3.1415926535897932384626433d0, & ! pi 
    twoPi = 6.283185307179586476925287d0, &    ! 2 pi 
    pid2 = 1.570796326794896619231322d0, &     ! pi/2 
    rad = 0.01745329251994329576923691d0, &    ! pi/180 
    degs = 57.29577951308232087679815d0, &     ! 180/pi 
    logten = 2.302585092994045684017991d0, &   ! ln(10) 
    c = 2.997925d5, &                          ! speed of light in vacuum, km/s 
    earthr = 6371.0990d0, &                    ! earth radius, km 
    plat = 1.37183d0, &                        ! magnetic pole latitude 
    plon = -1.21824d0 )                        ! magnetic pole longitude 

type subType
    real(kind=8) :: a, b
end type

type xType 
    logical :: flag1, flag2
    real(kind=8) :: scalar1, scalar2 
end type

type yType
    logical :: flag1, flag2 
    integer :: val1, val2
    type(subType) :: badIdea
end type

end module genParamsMod 

module propMod 

use genParamsMod 
implicit none 

contains 

subroutine initArray(var1,var2,o1, o2) 
real(kind=8), dimension(:), intent(inout) :: var1, var2
type(xType), intent(inout) :: o1
type(yType), intent(inout) :: o2 
!$acc routine seq 

var1 = twopi 
var2 = logten

o1%scalar1 = 0.0d0 
o1%scalar2 = pi 
o1%flag1 = .true.
o1%flag2 = .false.

o2%val1 = 0
o2%val2 = 2
o2%flag1 = .false.
o2%flag2 = .true.
o2%badIdea%a = 1.0d0
o2%badIdea%b = 2.0d0

end subroutine 

end module

When I went through and “hollowed out” the above code such that all the non-scalar arguments were removed from initArray, there were (not surprisingly) no compiling errors. It was okay with o1, but as soon as I added the argument o2 , I got the error that module variables need to be included in a !$acc declare create() directive. Given your comments about scope, it seems that I’d need to add that directive in genParamsMod, but I don’t know for what – no variables are being initialized there, only in the subroutine using types defined in the module. For grins I added "!$acc declare create(o1, o2) to the subroutine initArray, that didn’t help, either.
So, as my cheeky subtype name indicates, I should probably figure out an alternative to having defined types whose components include defined types. This should be an easy fix, but I’d still welcome any tips that may help the compiler deal with this little mess.
Thanks for your help, both already given and any you might give yet!
Best regards, -Stephen (sdl)

Hi Stephen,

The “o1” and “o2” variable should be fine as well since they are being passed in. You only need to use “declare create” for module variables that are used directly in the routine and not passed in.

I tried compiling your code but didn’t see the problem. I did get a different error because the compiler is trying to call a CPU call to memset, but this can be avoided by adding the flag “-Mnoidiom”.

% pgfortran -c test.F90 -Minfo=accel -ta=tesla:cc60 -Mnoidiom -V17.10
initarray:
     39, Generating acc routine seq
         Generating Tesla code

Which compiler version and OS are you using?

-Mat

Hello,
After digging deeper I found that at least 2 defined types, which are both defined in a module, are causing the compiler to complain about needing an !$acc declare create() directive. (Note, again, that no variables are declared in that module, aside from a couple parameter()). And, although it’s probably a bad practice to “nest” defined types as I described in my last update, that did not turn out to be the problem – I modified the code to avoid doing that. But the compiler error persisted after that change. After stumbling around a bit more, I found that, in one of them, it was a couple of allocatable scalar arrays causing the error. As those allocatable arrays are part of our “way forward” development with this model and are not currently critical, I just removed those and one of the errors went away. Based on that finding, my guess is that one (at least) of the other two (so far) errors is caused by a handful of assumed dimension arrays of scalar pointers contained in the other defined type. Here’s the excerpted types from the actual module in its current form:

module ionParamsMod
implicit none 
type hfRayP

    ! X/O, freq, init and fin positions
    real(kind=dp) :: mode, freq, initHt, initLat, initLon, &
        initdA1km, rxRng, rxBrng, perigee
    real(kind=dp), pointer :: apogee, initElev, initAz => null()
    integer :: TxNode, RxNode
    integer, pointer :: nHops, nPts => null()
    ! record below values at receiver height for each hop (e.g. approx 12 pts each)
    real(kind=dp), dimension(:), pointer :: doppler, absorb, gpl, ppl, rpl, finAz, &
        finElev, finLat, finLon, finRange, dS, dA, transLoss, spreadLoss, reflLoss => null()
    integer, dimension(:), pointer :: nRef => null()
    ! for optionally plotting ray paths (e.g. 400 points along path each var)
    real(dp), dimension(:), pointer :: rayheight, rayrange, elev, az, dAz, lat, lon, &
        dDopp, dAbsorb, dGPL, dPPL, dRPL, ddA => null()
    ! (Doppler, absorption, Group, Phase and Geom path lengths each segment.)
    ! polarization at receiver height for each hop.
    complex(kind=cdp), dimension(:), pointer :: polar, lpolar => null()
    complex(kind=cdp), dimension(:), pointer :: pathPolar, pathLpolar => null()
end type 

type appleZ ! Z parameter of Appleton dispersion formula
    real(kind=dp) :: capZ, pzpr, pzpth, pzpph
    character(len=16) :: model
    integer :: modelType
    character(len=120) :: modelFile
    character(len=24) :: envModel
    ! not there yet: (also, causing compiler to complain about declare create()???
    real(kind=dp), dimension(:), allocatable :: nu, dnudz
    !type(expParams) :: expLayer
    real(kind=dp) :: nu1, h1, a1, nu2, h2, a2, constZ

end type 
end module

This program then works like this: When built as a library, the outermost code takes a structure of initialization parameters, and several arrays containing the background data, and several additional arrays in which it will put the results of the computation (it’s a wave propagation model). For each instance of the propagatoin modeling (the number of instances and initial values for each are contained in the input parameters), a chain of subroutines models the waves, and at steps along the way, records the results in the output arrays. At the beginning of each of thees instances, the initArray routine I sketched in my previous comments sets initial values, but also assigns pointers in the above defined type to the proper “slice” (a contiguous subset) of each of the output arrays.
I can sketch out the code in a little more detail if that will help, but the subroutines that are causing the error (so far) are where the hfRayP type are initialized (pointers assigned) or passed along to the subroutine that “records” the values in the output arrays (via the pointers).
Any additional hints?
Thanks so much!
-Stephen

Hi Stephan,

For the specific question of where you need to add declare create, having a small reproducing example would be very helpful. It’s fine to put allocatable scalars in a “declare create” clause, you just need to add it to the same module where the variables are declared and then update the device values at the same time you update the host. If you are modifying the scalars on the device, then this would cause a race condition, but read-only access is fine.

For the larger question on how best to port the code to the GPU, that might be better taken off line. Are you able to share the full source? If so, please send it to PGI Customer Service (trs@pgroup.com) and ask them to send it to me. Though, I’ll be at the Supercomputing conference next week, and then with Thanksgiving after, it might be a bit before I can take a look.

-Mat

Hi Mat,
Can never thank you enough for your help, in all forms!
Yes, at this point I think it may be most productive to send you a larger chunk of the code, as I’m getting the sense that the errors and issues coming up are perhaps inter-related, and a wider view by better trained eyes will be most helpful. Thanks.
One layer (subroutine, !$acc routine) up from the issue in this thread is the set of loops I’m trying to parallelize on the GPU. After commenting out any offending lines related to the !$acc declare create() error in an attempt to debug in parallel, I’m getting the error

Unsupported nested compute construct in compute construct or acc routine

for the following nested loops:

    !$acc parallel
    !$acc loop collapse(3) private(ii, jj, kk, irij, deltaAzIJ, rxVecIJ, omega)
    azloop: do kk = 1,nTheta !  azimuth

        vertLoop: do jj = 1,nPhi

            freqLoop: do ii = 1,nFreq

                irij = 0

                ! for 3D power flux estimates: stagger vertically stacked rays so that
                ! the area of polygons (triangles) formed by neighboring rays near the
                ! transmitter is non-zero.
                deltaAzIJ = dsin(dble(jj-1)*pi*0.5d0)
                if (dabs(deltaAzIJ).lt.1.0d-12)  deltaAzIJ = 0.0d0
                rxVecIJ = (/rxRng, rxBrng + thVec(kk) + deltaAz*deltaAzIJ, rxHt/)

                omega = twoPi * fvec(ii) * 1.0d6

                ! trace(TxIn, RxVec, g, g1, omega, oxMode, elevAng, inCountVec, iono, ir, &
                !    finElev, finAz, finLat, finLon, ppl, rpl, gpl, absorb, doppler, &
                !    finRange, dS, polar, lpolar, nRef, rayheight, rayrange, lat, lon, &
                !    elev, dAz, az, dPPL, dGPL, dRPL, dAbsorb, dDopp, &
                !    pathPolar, pathLpolar )
                call trace(txVec, rxVecIJ, g, g1, omega, oxMode, phVec(jj), &
                        maxHops, ionoParams, xVec, yVec, zVec, Ne, xd, yd, zd, xdp, &
                        ixRow, iyRow, izRow, irij, &
                        finElev(:,ii,jj,kk), finAz(:,ii,jj,kk), finLat(:,ii,jj,kk), & 
                        finLon(:,ii,jj,kk), finppl(:,ii,jj,kk), &
                        fingpl(:,ii,jj,kk), finrpl(:,ii,jj,kk), finAbsorb(:,ii,jj,kk), &
                         finDoppler(:,ii,jj,kk), &
                        finRange(:,ii,jj,kk), finDS(:,ii,jj,kk), finDA(:,ii,jj,kk), &
                        finPolar(:,ii,jj,kk), finLpolar(:,ii,jj,kk), &
                        rayApogee(ii,jj,kk), rayInitElev(ii,jj,kk), rayInitAz(ii,jj,kk),&
                        rayNpts(ii,jj,kk), rayNhops(ii,jj,kk), rayNRef(:,ii,jj,kk), &
                         rayHeight(:,ii,jj,kk), rayRange(:,ii,jj,kk), &
                        rayLat(:,ii,jj,kk), rayLon(:,ii,jj,kk), rayElev(:,ii,jj,kk),&
                        raydAz(:,ii,jj,kk), &
                        rayAz(:,ii,jj,kk), raydPPL(:,ii,jj,kk), raydGPL(:,ii,jj,kk), &
                        raydRPL(:,ii,jj,kk), raydAbsorb(:,ii,jj,kk), &
                        raydDopp(:,ii,jj,kk), rayPolar(:,ii,jj,kk), rayLpolar(:,ii,jj,kk) )

                if (irij.ne.0) ir = irij
            enddo freqLoop
        enddo vertLoop
    enddo azLoop
    !$acc end parallel

I’ve tried various combinations of worker/gang/vector/independent clauses, too. Trace and everything below are !$acc routine seq. The large arrays in the argument list are the output of the program, and are eventually copied back to the host and returned to the calling program. All those array portions are what the hfRayP defined type mentioned previously points to, btw.
Anyway, I’ll also send the code along. Profuse thanks for any time you sink into these issues. No worries about any delay in response – enjoy the conference, and have a happy Thanksgiving! I’ll be away for part of the next two weeks, as well.
-Stephen
P.S. Good work on the book (ed. Rob Farber) – I’m enjoying it and learning more.