MODULE basis_m
implicit none
TYPE basis_t
real :: a
TYPE (basis_t), allocatable :: tab_basis(:)
END TYPE basis_t
END MODULE basis_m
With gfortran, the compilation works fine and I’m using this kind of structure without trouble. However, with nagfor, I obtain:
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7101
Evaluation trial version of NAG Fortran Compiler Release 7.1(Hanzomon) Build 7101
Segmentation violation
Internal error - please report this bug
The workaround is to use pointer instead allocatable and I did use pointer attribute for years for such data structure, but I prefer use allocatable whenever it is possible.
Of course, there is a bug with nagfor and I’ll send a report.
However, I wondering if the piece of code is correct ?
It is compilable by gfortran (as opposed to the similar code where TYPE(basis_t) gets replaced by CLASS(basis_t) ) but are you sure it is working properly? According to the first of cited posts, gfortran-compiled recursive DTs give wrong results in execution.
A test with just a recursive writing subroutine is working well with gfortran.
MODULE basis_m
implicit none
TYPE basis_t
real :: a
TYPE (basis_t), allocatable :: tab_basis(:)
END TYPE basis_t
CONTAINS
RECURSIVE SUBROUTINE Write_Basis(Basis)
TYPE(Basis_t), intent(in) :: Basis
integer :: i
write(6,*) '-------------------------------------------------'
write(6,*) 'Write_Basis'
write(6,*) 'a',Basis%a
IF (allocated(Basis%tab_basis)) THEN
DO i=1,size(Basis%tab_basis)
CALL Write_Basis(Basis%tab_basis(i))
END DO
END IF
write(6,*) '-------------------------------------------------'
END SUBROUTINE Write_Basis
END MODULE basis_m
PROGRAM test
USE basis_m
implicit none
TYPE(basis_t) :: basis
basis%a = 1.
allocate(basis%tab_basis(2))
basis%tab_basis(1)%a = 1.1
basis%tab_basis(2)%a = 1.2
CALL Write_Basis(basis)
END PROGRAM test
The results are as expected:
-------------------------------------------------
Write_Basis
a 1.00000000
-------------------------------------------------
Write_Basis
a 1.10000002
-------------------------------------------------
-------------------------------------------------
Write_Basis
a 1.20000005
-------------------------------------------------
-------------------------------------------------
You have access to NAG technical support for the period of your trial. I can confirm that the latest Build (7106) of the NAG Fortran Compiler Release 7.1 does not have this bug.
While this case worked fine with gfortran, I’d advise against using this kind of structure with gfortran since it still can be buggy and provide wrong results or segfaults.
I ended up here looking if it was a known problem when my code with recursive derived types segfaulted just because moved a block of code in my main program to a function (to use as a constructor of these types)