Why do I keep getting "managed attribute mismatch" in my routine calls?

I am trying to compile a codebase with nvfortran, but I am currently stuck on some “managed attribute mismatched” errors, how can I find the cause of this? The errors are there even when no attribute is added to the variable declaration, and is still present if I add the managed attribute to both the variable declaration and the subroutine parameter.

The code looks something like this

complex(dp), managed, allocatable :: hdgAinv(:,:)

....

call hdg_build_Ainv_1D_line(hdgAinv,                              &
                   ctx_dg%vol_matrix_mass(i_order_cell)%array,          &
                   ctx_dg%vol_matrix_dphi_phi(i_order_cell)%array,      &
                   sumface_phii_phij,ctx_dg%inv_jac(:,:,i_cell),        &
                   ctx_dg%det_jac(i_cell),kappa,rho,ndof_vol,           &
                   freq,ctx_dg%pml_cell_coeff(:,i_cell),ctx_err)

subroutine hdg_build_Ainv_1D_line(Ainv,vol_phi_phi,vol_dphi_phi,      &
                                    sumface_phii_phij,inv_jac,det_jac,  &
                                    kappa,rho,ndof_vol,freq,pml_coeff,  &
                                    ctx_err)
    implicit none
    
    complex(dp),     managed  ,intent(inout):: Ainv(:,:)
    real   (kind=RKIND_POL)       ,intent(in)   :: vol_phi_phi(:,:)
    real   (kind=RKIND_POL)       ,intent(in)   :: vol_dphi_phi(:,:,:)
    complex(dp),    managed,  allocatable  ,intent(in)   :: sumface_phii_phij(:,:)
    real(dp)                      ,intent(in)   :: inv_jac(:,:)
    real(dp)                      ,intent(in)   :: det_jac
    complex(dp)                   ,intent(in)   :: kappa
    real(dp)                      ,intent(in)   :: rho
    complex(dp)                   ,intent(in)   :: freq
    complex(dp)                   ,intent(in)   :: pml_coeff(:)
    integer                       ,intent(in)   :: ndof_vol
    type(t_error)                 ,intent(inout):: ctx_err

This is not the only routine where I get the error, but I’m getting

NVFORTRAN-S-0536-Argument number 1 to hdg_build_ainv_1d_line: managed attribute mismatch (/.../m_create_matrix_refelem.f90: 369)
NVFORTRAN-S-0536-Argument number 4 to hdg_build_ainv_1d_line: managed attribute mismatch (/.../m_create_matrix_refelem.f90: 369)

I had this error with no managed attributes at the start, I tried to add managed to each of them, both in their declaration and the parameter, but I still get this error, am I missing something?

First, make sure that the interface to hdg_build_Ainv_1D_line is explicit at the call site. I rarely use managed on the dummy arguments, and usually use “device”, so there could be a bug here. If the dummy argument has the device attribute, it will match both device and managed actual arguments. You might try that as a work-around, and if that works, we probably have a bug in the compiler.

I found that this error only happens due to the function call being inside an OpenMP loop

I managed to simplify it to a minimal reproducible example, the key is that the function definition has an allocatable attribute inside a routine called by OpenMP. In my case, having the parameters as allocatable is incorrect, so I don’t know if this should be considered a bug or intended behavior, for sure the error message could be more helpful

program main
    use iso_fortran_env, only: dp => real64
    implicit none

    call openmp_func()

    contains

    subroutine test_func(Ainv)
        complex(dp), allocatable, intent(inout) :: Ainv(:,:)

        Ainv = cmplx(0.0_dp, 1.0_dp, kind=dp)
    end subroutine test_func

    subroutine openmp_func()
        complex(dp), allocatable :: Ainv(:,:)
        integer :: i

        allocate(Ainv(10,10))

        !$omp parallel private(Ainv)
        !$omp do
        do i = 1, 10
            call test_func(Ainv)
        end do
        !$omp end do
        !$omp end parallel
    end subroutine openmp_func
end program main

And the following compilation throws this error

(.venv) ➜  arborescence-compil git:(stdpar) ✗ nvfortran -cuda -mp -stdpar=gpu managed_mismatch.f90
NVFORTRAN-S-0536-Argument number 1 to test_func: managed attribute mismatch (managed_mismatch.f90: 24)
  0 inform,   0 warnings,   1 severes, 0 fatal for openmp_func

The error is fixed either by

  • removing the allocatable in the parameter definition
  • removing the -mp flag, disabling OpenMP
  • removing the -stdpar=gpu flag, which in this case is completely useless, but it is used elsewhere in the code to offload do concurrent loops, do you know why that would cause such a problem?

Thanks for the reproducer!

When using “-stdpar=gpu”, the default is to apply the “managed” attribute to all allocatables. What appears to be happening here is when “-stdpar=gpu” and “-cuda” are used together, the compiler isn’t propagating the managed attribute to the OpenMP private arrays. My best guess is that there is a logic conflict between what to do when “-stdpar=gpu” is used versus what happens with “-cuda”, though I’ll need engineering to investigate. I submitted an issue report, TPR #37570.

If you aren’t actually using CUDA Fortran, you can work around this by removing “-cuda”.

Alternatively, you can add the flag “-gpu=mem:separate”. This disables using “managed”. The caveat being that when you do use DC, you’ll need to manually managed the device data either through OpenACC directives or CUDA Fortran.

-Mat

I do use CUDA Fortran elsewhere, but I’ll keep in mind using separate memory if I encounter another case in the code base where I can’t simply remove the allocatable attribute, thanks!