Allocating array of derived type fails in SIGSEGV

I am trying to allocate an array of a derived type in a subroutine after I read in the size of the array from a file, but it fails in read_grid() when calling allocate(). It could be something silly I have not noticed, but I have been looking at this for a while now.
The derived type itself has some allocatable arrays of reals, maybe that is the issue? But then how do I initialise the array without knowing its size ahead of time?

The code in question (simplified with only the relevant bits)

      program solver
      use types
      implicit none
      type(t_grid), allocatable, dimension(:) :: g
      call read_grid(g)

!     continue with program
      end program myprogram

and read_grid.f90 has the following:

 
      subroutine read_grid(g)

      use types
      implicit none
      type(t_grid), allocatable, intent(out) :: g(:)
      integer :: n, no_grids, ni, nj

!     file IO happens here, this works fine

      read(2) no_grids
      write(6,*) '  Number of grids ', no_grids
!     no_grids gets read in fine
!     **** THIS IS WHERE SIGSEGV happens
      allocate(g(no_grids))

      do n = 1,no_grids

!         Allocate arrays in current element of g and read in values
          read(2) ni, nj
          g(n)%ni = ni; g(n)%nj = nj;
          write(6,*) '  Size of grid', n, 'ni =', ni, 'nj =', nj
    
!         Allocate and then read the coordinates
          allocate(g(n)%x(ni,nj),g(n)%y(ni,nj))
          read(2) g(n)%x; read(2) g(n)%y;
!         ... and so on with reading in everything else
      end do
      close(2)
      write(6,*)
      end subroutine read_grid

and the t_grid is defined as such in types.f90

      module types
      type t_grid
          integer :: ni, nj
          real, dimension(:,:), allocatable :: x, y
!         and lots of other 2D arrays
      end type t_grid

      end module types

The actual error after compiling with gfortran is ā€œProgram received signal SIGSEGV: Segmentation fault - invalid memory reference.ā€ and the backtrace points to the marked line read_grid.f90.

When building with -fcheck=all the error becomes: ā€œFortran runtime error: Allocatable actual argument ā€˜gā€™ is not allocatedā€ pointing to call read_grid() but I thought it was fine to allocate arrays in subroutines?
I am using gfortran 13.2.1 with flags -g -fbacktrace -fcheck=all
Iā€™m a bit new to using Fortran so any help is very much appreciated, and let me know if you need any other information.

I have certainly used an allocated derived type structure, as you outline.

I have been careful with deallocate, by first deallocating all allocatable components. I have done this as the compiler that I use warns that allocatable components may not be deallocated if the allocatable type ā€œgā€ is deallocated. I donā€™t know which version of the standard implies this problem.

Try removing ā€œintent(out)ā€ and manage any required deallocate yourself.

I have found this flexible data structure has been very effective in transferring a disk-based data structures to a memory-based structures. With 64 GBytes of installed memory, these old data-bases are now relatively small in comparison to available memory.

I just skimmed over your code, but I do not see where read_grid() has an explicit interface. That subroutine should be in a module somewhere, but the main program has no USE statement for it. A subroutine with an allocatable dummy argument must have an explicit interface.

3 Likes

That was it, I wrapped the subroutine in a module and added the use statement and everything works fine now. I think this fits the silly mistake category. Thank you so much for the help!