Allocation of variable of a type containing an allocatable array

Hello
(post edited after its first answer)
I am quite a newby to fortrans other than 77 (switch to a bit of C/C++ meanwhile). I want to have an allocatable array of a variable being of a type itself containing an allocatable array. Here is a minimal working example (actually not-working example :slight_smile: )

a module defining a type data_t:

module moduledataType
  type data_t 
  	integer :: size
  	real, allocatable :: data(: )
  end type data_t
contains 
end module moduledataType

the main program :

program main
  use moduleDatatype

  type(data_t), allocatable :: coef(: )
  
  call readValue(coef)

contains 

subroutine readValue(co)
  type(data_t), intent(inout), allocatable :: co
  real, allocatable :: tempData(: )
  type(data_t) :: coTemp
  integer :: nCo =5 
  integer :: nCoeff,i,j
 
  allocate(co(nCo)) 
  do i=1,nCo
    allocate(tempData(2*i)) 
    do j=1,2*i
    	tempData(j)=j
    enddo
    coTemp%size=2*i
    allocate(coTemp%data,source=tempData)
    co(i)=coTemp
  enddo  
   
end subroutine readValue

end program main

Notice that the data member of each element of coef have not the same allocation size.
Logically, the line

allocate(co(nCo))

does not work. How can it allocate an array of variable size elements ? Using a pointer ? In C++ I would have use a pointer or a container (and succed to do it a few years ago quite easily), but il looks like I am not as successful in fortran as pointers seem not to work the same way. I should probably get deeper into pointer use in fortran.

Can someone help me regarding how to fix my issue, please ?

Thanking you in advance

In the subroutine you have declared co as a scalar instead of an array co(:)

Your code is difficult te read, because it has no indentation. Here is a simplified and corrected version:

module moduledataType
   type data_t
      integer :: size
      real, allocatable :: data(: )
   end type data_t
end module moduledataType

program main
   use moduleDatatype

   type(data_t), allocatable :: coef(: )

   call readValue(coef)

contains

   subroutine readValue(co)
      type(data_t), intent(inout), allocatable :: co

      real, allocatable :: tempData(: )
      type(data_t) :: coTemp
      integer :: nCo =5   ! IMPLIED SAVE ! DO NOT DO THAT !
      integer :: i,j

      allocate(co(nCo))
      do i=1,nCo
         allocate(co(i)%data(2i))
         do j=1,2i
            co(i)%data(j)=j
         enddo
         co(i)%size=2*i
      enddo
      
   end subroutine readValue

end program main

Than you very much
Well sorry for the indentation. Of course, in my code, I wrote the example with indentation … but I used quote instead of code.
I am all the more sorry for co(: ) . I should have paid more attention. I feel like a dumb :slight_smile:

By the way, after correcting with some if(allocated()) allocate, it looks that things work just fine just seamlessly, even more easily than in C++. I am very surprized to successfully allocate(co(nCo)) and being able to change change the size of each element of co after this allocation.
I guess that I need finalazing each element of coef and coef afterwards as for destructors in C++ ?

allocate(co(nCo)) just allocates an array of type(data_t), it doesn’t allocate the components of each element.

Actually no, you don’t need to. All allocatable objects are automatically deallocated when they go out of scope (this is NOT the case for the pointer objects).

What I do not understand is that when you allocate memory a certain amount of bytes are allocated. When allocating 10 reals, 10 times sizeof(real) is given to the executing code. But in the present case, the amount of memory is not known in advance since there is an allocatable array inside each co. What is done in the memory ? A kind of pointer is hidden in the background ? It gives me the feeling of using a C++ vector container…

When a type contains an allocatable or pointer component, only a fixed size descriptor of this component is stored in the object itself, and the memory allocated by this component is stored separately. And ultimately, yes, the descriptor contains a classical C pointer under the hood.

1 Like

Thanx a lot PierU

Yes, fortran allocatable objects can be regarded as something described with an address pointer along with rank and bounds information. However, the language constrains the object in several ways, so the semantics of allocatables is different than the semantics of pointers. As a general rule, in fortran one uses allocatables when possible rather than pointers.

1 Like