Array of array component

The following code is not valid:

program foo
    implicit none
    type bar
        integer :: y(2)
    end type
    type(bar) :: x(10)

    x(:)%y(:) = 0
end program foo
    8 |     x(:)%y(:) = 0
      |    1
Error: Two or more part references with nonzero rank must not be specified at (1)

This works is either x or y (or both) is scalar. Is there any technical reason why this is not allowed when both are arrays?

I can understand why this is not allowed in the case y is allocatable or pointer, because the memory addresses would be completely random, but if y is a fixed sized array then x(:)%y(:) has a regular structure in memory and could be described as an array (of rank rank(x)+rank(y))

1 Like

What if the type bar contained other components of which at least one was allocatable/pointer?

In this case only the array descriptor is stored in the type itself, and it has a constant size. All elements of an array of a given type are supposed to have the same size in memory, forming a regular structure.

program foo
    implicit none
    type bar
        integer, allocatable :: z(:)
        integer :: y(2)
    end type
    type(bar) :: x(10)
    integer :: i

    do i = 1, size(x)
        allocate(x(i)%z(1000*i))
    end do
    print*, "storage size of bar:", storage_size(x)/8," bytes"
    do i = 2, size(x)
        print*, "offset between element",i-1," and", i," :",loc(x(i)%y) - loc(x(i-1)%y)
    end do
end program foo
 storage size of bar:          72  bytes
 offset between element           1  and           2  :                   72
 offset between element           2  and           3  :                   72
 offset between element           3  and           4  :                   72
 offset between element           4  and           5  :                   72
 offset between element           5  and           6  :                   72
 offset between element           6  and           7  :                   72
 offset between element           7  and           8  :                   72
 offset between element           8  and           9  :                   72
 offset between element           9  and          10  :                   72

I assume that in your code above you would also allow

x%y = 0

and in general would allow

a%b%c%d = 0

if the array components of the types all have fixed size. Then you would need to look up the declarations of all the types involved in an expression to determine the rank of the expression, which I think is a drawback to the proposal.

The relevant constraints in the standard:

C913 (R912) If a section-subscript-list appears, the sum of the rank of part-ref , the sizes of the arrays in each multiple subscript, and the number of subscripts, shall equal the rank of part-name.

C919 (R911) There shall not be more than one part-ref with nonzero rank. A part-name to the right of a part-ref with nonzero rank shall not have the ALLOCATABLE or POINTER attribute.

I agree that in your example the memory layout is regular and well known, but it will take some very careful wording and thought to relax those constraints just right to allow for this edge case. It would open the door to some potentially weird things. Like

x(1, 2:5, 3:7:2)%y(:, :, ::3)%z(:5, :, :)%w(:, :, :)%v(:, :, :)%u(:, :) = 0

The resulting “array” has a very weird striding pattern (probably ok), and rank 16 (larger than is promised to be supported by the standard). But I think what may really throw a monkey wrench in things is something like

x([1, 5, 4])%y(:) = 0

because that does not have a regular layout in memory.

I admit this could be challenging for the compilers and for the wording in the standard. But I’m not sure it’s an “edge case”.

It’s not very different from x([1, 5, 4]) = <scalar_of_the_same_type_as_x>, which is valid even though x([1, 5, 4]) has not a regular layout.

I have long wondered why these kinds of expressions are not allowed, even when y(:) is allocatable or a pointer. It is equivalent to something like

do concurrent (i = 1:size(x))
   do concurrent (j = 1:size(x(i)%y))
      x(i)%y(j) = 0
   enddo
enddo

Why can’t the compiler do that for me rather than me having to type all of that? I understand, of course, that the storage might not be regularly spaced within memory, but what does that really have to do with whether or not the expression is well defined? And if the expression is well defined, and it gives the programmer the ability to clearly specify the operation, then why should it be not allowed?

Here is a corrected version which compiles and runs:

ian@ian-Latitude-E7440:~$ f77 foofix.f -ffree-form
ian@ian-Latitude-E7440:~$ ./a.out
ian@ian-Latitude-E7440:~$ cat foofix.f
program foo
    implicit none
    type bar
        integer :: y(2)
    end type bar
    type(bar) :: x(10)
    integer :: i

    do i = 1, 10
        x(i)%y = 0
    end do
end program foo
ian@ian-Latitude-E7440:~$ 

Thanks, but I know how to make it run, that was not the point.