Use of declare create for a structured variable

In a Fortran module (hereafter, MESH_TYPES), I am defining a rather complex structure for handling a mesh type variable, which is partly shown below:

TYPE mesh_structure
INTEGER(C_INT) :: nVert, nCell

REAL(C_DOUBLE) :: hAvg, hMax, hMin

TYPE(vertex), DIMENSION(:), ALLOCATABLE :: Vert

TYPE(cell), DIMENSION(:), ALLOCATABLE :: Cell
END TYPE mesh_structure

I then have the following routine that I need to copy in the device memory:

SUBROUTINE COMPUTE_LINEAR_TET_MAPPING_COEFFICIENTS(vertices, mapCoeff)
!------------------------------------------------------------------
!$ACC ROUTINE SEQ
!------------------------------------------------------------------
!---- Shared modules
!------------------------------------------------------------------
USE MESH_TYPES
!------------------------------------------------------------------
!---- I/O variables
!------------------------------------------------------------------
INTEGER(C_INT), DIMENSION(:), INTENT(IN) :: vertices

REAL(C_DOUBLE), DIMENSION(:,:), ALLOCATABLE :: mapCoeff
!------------------------------------------------------------------
!---- Local variables
!------------------------------------------------------------------
REAL(C_DOUBLE), DIMENSION(3) :: v1, v2, v3, v4
!------------------------------------------------------------------
!---- Testing for bad input
!------------------------------------------------------------------
IF (ALLOCATED(mapCoeff)) DEALLOCATE(mapCoeff)
!------------------------------------------------------------------
!---- Allocate and initialize
!------------------------------------------------------------------
ALLOCATE(mapCoeff(3,4))
mapCoeff(:,:) = 0.0
!
v1(:) = Mesh%Vert(vertices(1))%coor(:)
v2(:) = Mesh%Vert(vertices(2))%coor(:)
v3(:) = Mesh%Vert(vertices(3))%coor(:)
v4(:) = Mesh%Vert(vertices(4))%coor(:)
!------------------------------------------------------------------
!---- Compute coefficients
!------------------------------------------------------------------
mapCoeff(:,1) = v1(:)
mapCoeff(:,2) = v2(:) - v1(:)
mapCoeff(:,3) = v3(:) - v1(:)
mapCoeff(:,4) = v4(:) - v1(:)
!------------------------------------------------------------------
END SUBROUTINE COMPUTE_LINEAR_TET_MAPPING_COEFFICIENTS

In order to successfully compile this routine, I (apparently) need to insert a “DECLARE CREATE” pragma for the global variable “Mesh”, which I have done just after the declaration of this variable in module MESH_TYPES:

TYPE(mesh_structure) :: Mesh
!$ACC DECLARE CREATE(Mesh)

Now, I have a problem when linking a program that makes use of module MESH_TYPES.

[ 48%] Building Fortran object app/add_mesh_boundary/CMakeFiles/add_mesh_boundary.dir/add_mesh_boundary.f90.o
[ 48%] Linking Fortran executable …/…/bin/add_mesh_boundary
nvlink error : Undefined reference to ‘_mesh_types_16’ in ‘CMakeFiles/add_mesh_boundary.dir/add_mesh_boundary.f90.o’
pgacclnk: child process exit status 2: /home/lanteri/opt/pgi/linux86-64-llvm/19.10/bin/pgnvd

I suspect that this is due to the fact that I am using the DECLARE CREATE before having allocated the
allocatable components of the variable Mesh.

Could you please give me some hints for solving this problem?

Thanks a lot in advance!

Hi sl06,

Unfortunately, without a reproducing example, it’s difficult for me to tell what’s wrong. Though, the first thing to check is if the mesh_type.o object file is being included in the link. Can you post the full link line being used?

-Mat

Hi Mat,

I have tried to reproduce the problem with a simple example.

File modpi_oacc.F90 contains the following:

MODULE MODPI

TYPE cell_structure
INTEGER :: idcell
END TYPE cell_structure

TYPE mesh_structure
TYPE(cell_structure), DIMENSION(:), ALLOCATABLE :: pitab
END TYPE mesh_structure

TYPE(mesh_structure) meshpi
!$ACC DECLARE CREATE(meshpi)

END MODULE MODPI

File pitab_oacc.F90 contains the following:

SUBROUTINE FILL_PITAB
!$ACC ROUTINE SEQ

USE MODPI

IMPLICIT NONE

INTEGER :: i

DO i=1,10000
meshpi%pitab(i)%idcell = 10000 + i
ENDDO

END SUBROUTINE FILL_PITAB

Finally, the main program test_oacc.f90:

PROGRAM TEST_OACC

USE MODPI

IMPLICIT NONE

CALL FILL_PITAB

END PROGRAM TEST_OACC

I am not including an OpenACC pragma in the main program.

pgf90 -O3 -acc -Minfo=all -c modpi_oacc.F90 -o modpi_oacc.o
pgf90 -O3 -acc -Minfo=all -c pitab_oacc.F90 -o pitab_oacc.o
fill_pitab:
1, Generating acc routine seq
Generating Tesla code
10, Loop unrolled 2 times
pgf90 -O3 -acc -Minfo=all -c test_oacc.F90 -o test_oacc.o
pgf90 -O3 -acc -Minfo=all modpi_oacc.o pitab_oacc.o test_oacc.o -o test_oacc.exe
nvlink error : Undefined reference to ‘_modpi_16’ in ‘modpi_oacc.o’

If I use a static array for pitab:
TYPE(cell_structure), DIMENSION(1000) :: pitab
then I do not face this problem.

Hi sl06,

Try changing the “DECLARE CREATE” to a “DECLARE COPYIN”. It links for me after I make this change.

I think the difference is with create, only space is made available for meshpi, while with copyin, it also sets up phiab.

-Mat

Thanks Mat!

It is also working for me.

Now, I am slightly modifying the program test_oacc.F90 as:

PROGRAM TEST_OACC

USE MODPI

IMPLICIT NONE

INTEGER :: i

!$ACC PARALLEL LOOP
DO i=1,10
CALL FILL_PITAB
ENDDO

END PROGRAM TEST_OACC

and I have the following error:
pgf90 -O3 -DVAL_N=30000000 -acc -Minfo=all -c test_oacc.F90 -o test_oacc.o
PGF90-S-0155-Procedures called in a compute region must have acc routine information: fill_pitab (test_oacc.F90: 11)
PGF90-S-0155-Accelerator region ignored; see -Minfo messages (test_oacc.F90: 9)
test_oacc:
9, Accelerator region ignored
10, Loop not vectorized/parallelized: contains call
11, Accelerator restriction: call to ‘fill_pitab’ with no acc routine information
0 inform, 0 warnings, 2 severes, 0 fatal for test_oacc

Although I have the following i the called routine definition:

SUBROUTINE FILL_PITAB
!$ACC ROUTINE SEQ

Thanks again!

I’m assuming fill_ptab doesn’t have an interface and isn’t in a module? In that case F77 style calling conventions are used so the compiler has no information about fill_ptab. To fix, add another routine directive in the main program so that knows it has a device version of the routine, something like:

PROGRAM TEST_OACC

USE MODPI

IMPLICIT NONE

INTEGER :: i
!$ACC ROUTINE(FILL_PITAB) SEQ

!$ACC PARALLEL LOOP
DO i=1,10
CALL FILL_PITAB
ENDDO

END PROGRAM TEST_OACC

Hope this helps,
Mat

Hi Mat,

Yes it helps, thanks!

Stéphane