Automatic array of derived type with allocatable component

Hello, this is my first post here, so I hope this is the right section for this topic and that the formatting is ok.

I am having a bit of trouble understanding the behavior of the following code when it is compiled with gfortran.

module type
    implicit none
    type, public :: test_type
        logical :: aloc
        integer :: size
        double complex, dimension(:),allocatable :: elements

        contains
        procedure :: setup => setupType
    end type test_type

    contains

    subroutine setupType(this,size,aloc)
        class(test_type), intent(inout) :: this
        integer, intent(in) :: size
        logical, intent(in) :: aloc

        this%size = size
        this%aloc = aloc

        if (this%aloc) then
            allocate(this%elements(this%size))
        end if
    end subroutine setupType
end module type
    
module use_type
    use type
    implicit none
    integer :: n
    type(test_type), dimension(:), allocatable :: type_example
    
    contains
    function test_func()
        type(test_type),dimension(n) :: test_func
        !type(test_type),dimension(:), allocatable :: test_func

        integer :: i

        !allocate(test_func(n))

        do i  = 1,n
            call test_func(i)%setup(2,.false.)
            write(6,*) allocated(test_func(i)%elements)
        end do
        
    end function test_func
end module use_type
    
program test
use type
use use_type

implicit none

n = 2
call do_stuff()

contains
subroutine do_stuff()
    implicit none
    type(test_type),dimension(:),allocatable :: test_array,test_array_2

    test_array = test_func()
    type_example = test_func()

    test_array_2 = test_array
    type_example = test_array
    
    write(6,*) 'Hello!'

end subroutine do_stuff

end program

When compiling with gfortran (11.4), valgrind warns about a conditional jump or move depending uninitialized values from the line

type_example = test_array

in the do_stuff() subroutine, and that the uninitialized value originates from the line

type_example = test_func()

Valgrind also warns that the write statement in the test_func() function depends on an uninitialized value, but only when the function result is assigned to the type_example variable, which is stored in the module use_type. If I compile with -fsanitize=address, then the allocation check returns true for the second call of test_func() even though the elements components have not been allocated, and the program segfaults when it reaches

type_example = test_array

This seems to be the case also with later versions of gfortran when I test on compiler explorer.

If I compile with ifx instead, then everything is fine, and also if I use an allocatable instead of automatic array inside test_func(). So I am wondering if this is a bug with how gfortran handles functions returning automatic arrays that contain a derived type with an allocatable component, or if I am missing something?

The reason why I am interested in this, is that in a larger program that I am contributing to there are some functions that use automatic arrays of derived types similar to the one above. When running the program there are some strange downstream segfaults and calls to allocated() that return .true. before %elements have been allocated, when the results of those functions are assigned to a module variable. The problems seem to disappear when the functions are modified to use allocatable instead of automatic arrays.

1 Like

I remember Gfortran had some issue related to the use of a function name as the result variable (when it is a “complicated” variable), so it may be useful to declare the result variable explicitly…? (CompilerExplorer)

    function test_func() result(res)
        type(test_type),dimension(n) :: res
        integer :: i

        do i  = 1,n
            call res(i)%setup(2,.false.)
            write(6,*) allocated(res(i)%elements)
        end do
        
    end function test_func

By the way, the above code gives the “F F F F Hello!” for all ifort versions and ifx <= 2023.1.0 (with -check all), while ifx >= 2023.2.1 does not give the result (just returning 1 and no output). I am not sure what’s happening here…

1 Like

Thank you very much, explicitly declaring the result seems to fix things on my end, and I guess that’s a useful thing to do regardless.

With ifx it works with 2024.2 on my local machine (with or without -check all), but not on compiler explorer with the later versions as you say, but that seems related to the compilation step (the error message says that the linker can’t find msan if I understand correctly)

2 Likes