Are zero-length arrays OK

Wondering if it is OK if a program allows zero-length arrays. For example

    real(dp), allocatable :: aa(:), bb(:)
    integer :: i
    
    allocate(aa(0))
    bb = aa
    
    aa = 2.0_dp
    
    do i = 1,size(aa)
      print*,aa(i)
    enddo

I am wondering if this is equivalent to

    len_aa = 0
    if (len_aa > 0) then
      allocate(aa(len_aa))
      bb = aa
    endif
    if (len_a > 0) then
      
      aa = 2.0_dp
      do i = 1,size(aa)
        print*,aa(i)
      enddo
    endif

I prefer the first bit of code because it means I don’t have to do a bunch of if checks, which I might mess up.

It is. You do not need to treat zero-size arrays as a special case.

2 Likes

Nicholas has raised some subtle problems with allocation by assignment. I have modified it to show what happens when assigning a scalar or array value to an allocatable array that was either
allocated or not allocated beforehand, and removed dp and i. The program works with both gfortran and ifort. I commented out the declaration of and assignment to ee to make the program useful. Remove the ! from “! ee” in the two places it occurs if you want to see what your compiler then complains about.

   program arraysize
     implicit none
     real, allocatable :: aa(:), bb(:),cc(:),dd(:) ! ee(:)
     
     allocate(aa(0),cc(0))
     bb = aa
     
     aa = 2.0   ! previously size 0
     cc = [2.0] ! previously size 0
     dd = [2.0] ! previously unallocated
!  ee = 2.0     ! illegal assignment of scalar to unallocated array 
     call whatis(aa,'aa')
     call whatis(bb,'bb') ! unallocated, unassigned to
     call whatis(cc,'cc')
     call whatis(dd,'dd')
   contains
     
     subroutine whatis (array, arrayname)
       real,intent(in):: array(:)
       character(*),intent(in):: arrayname
       print*,arrayname,' size=',size(array), array
     end subroutine whatis
   end program arraysize

If you mean why “aa=2.0” does not cause an error, I have had that
discussion before. Intuitively, that seems like an error (it did to
me!). But the standard says the shape of a scalar data entity is an
array with rank one and size zero, and for intrinsic assignments

Execution of an intrinsic assignment causes, in effect, the evaluation
of the expression expr and all expressions within variable (7.1),
the possible conversion of expr to the type and type parameters of
the variable (Table 7.11), and the definition of the variable with the
resulting value. The execution of the assignment shall have the same
effect as if the evaluation of expr and the evaluation of all expressions
in variable occurred before any portion of the variable is defined by
the assignment. The evaluation of expressions within variable shall
neither affect nor be affected by the evaluation of expr . No value
is assigned to the variable if it is of type character and zero length,
or is an array of size zero.

So, in previous arguments where I thought that was a bug, I have been
told that is the proper behavior (after the assignment, aa is still a
zero length array.

PS. For setting an array to size zero, I often use the syntax “a=[real::]”, as you do not have to check and deallocate first in more complex situations. That sets a to a zero-size array even if already allocated.

2 Likes