Take the following example and the latest nvfortran
compiler version 24.7:
PROGRAM main
IMPLICIT NONE
REAL, ALLOCATABLE :: array(:)
ALLOCATE(array(1000))
CALL test_class(array)
CALL test_real(array)
CALL test_class(array(100:200))
CALL test_real(array(100:200))
CONTAINS
SUBROUTINE test_class(arg)
! Subroutine arguments
CLASS(*), INTENT(in) :: arg(:)
SELECT TYPE (arg)
TYPE IS (REAL)
WRITE(*,*) "Lower bound of CLASS(*) arg: ", LBOUND(arg)
CLASS DEFAULT
WRITE(*, *) "Not REAL"
END SELECT
END SUBROUTINE test_class
SUBROUTINE test_real(arg)
! Subroutine arguments
REAL, INTENT(in) :: arg(:)
WRITE(*,*) "Lower bound of REAL arg: ", LBOUND(arg)
END SUBROUTINE test_real
END PROGRAM main
All compilers I tried (gfortran
, ifort
, ifx
, nagfor
) besides nvfortran
works as expected and give the same result:
Lower bound of CLASS(*) arg: 1
Lower bound of REAL arg: 1
Lower bound of CLASS(*) arg: 1
Lower bound of REAL arg: 1
With nvfortran
there seems to be a bug when a slice is passed in the CLASS(*)
argument of test_class
:
Lower bound of CLASS(*) arg: 1
Lower bound of REAL arg: 1
Lower bound of CLASS(*) arg: 0
Lower bound of REAL arg: 1
I tried to manually specify the lower bound in the dummy argument specification (CLASS(*), INTENT(in) :: arg(1:)
) but that did not work, nothing changed.
Another variant of the same problem can be seen with an adapted example:
PROGRAM main
IMPLICIT NONE
REAL, ALLOCATABLE :: array(:)
ALLOCATE(array(1000))
CALL test_class(array)
CALL test_real(array)
CALL test_class(array(100:200))
CALL test_real(array(100:200))
CONTAINS
SUBROUTINE test_class(arg)
! Subroutine arguments
CLASS(*), INTENT(in) :: arg(2:) ! Differ from original example here
SELECT TYPE (arg)
TYPE IS (REAL)
WRITE(*,*) "Lower bound of CLASS(*) arg: ", LBOUND(arg)
CLASS DEFAULT
WRITE(*, *) "Not REAL"
END SELECT
END SUBROUTINE test_class
SUBROUTINE test_real(arg)
! Subroutine arguments
REAL, INTENT(in) :: arg(2:) ! Differ from original example here
WRITE(*,*) "Lower bound of REAL arg: ", LBOUND(arg)
END SUBROUTINE test_real
END PROGRAM main
This example should give all 2
as lower bound (all working compilers mentioned above does indeed give that) as lower bound, but nvfortran gives:
Lower bound of CLASS(*) arg: 1
Lower bound of REAL arg: 2
Lower bound of CLASS(*) arg: 0
Lower bound of REAL arg: 2
Here both line 1 and 3 is incorrect, they should be 2
.
The “practical consequence” of this is that you will be out-of-bounds when accessing array members, which is of course completely spoiling whatever you are trying to compute.
This seems to be a compiler bug in nvfortran
. Any comments? Thanks in advance.