Array Bounds Checking - Standard Behavior?

I’m testing out the following dummy program. It seems that for any value entered by the user besides 1 and 2 (which yield 1 and 2), 0 is returned and the program does not crash.

program main
  implicit none
  integer :: x, z(2)
  z = [ 1, 2 ]
  write (*, *) 'Enter index of the array: '
  read *, x
  print *, z(x)
end program main

This came from an investigation on translating some legacy Fortran code to C# - we have an expression V(some_array(SOME_CONST)), where some_array(SOME_CONST) evaluates to 0 (really - it’s initialized to that). My experience in the C world is that native code would segfault or produce garbage. I’m trying to figure out whether the C# code needs to handle a special case here or not.

I’m trying to understand if the original author of this code (long since retired :wink:) was relying (un)standard behavior, or if this is a true bug. The original code uses ifort, and the little program above was compiled with gfortran on Replit. For both V(0) == 0 (V’s lower bound is 1).

  • Does the standard define a behavior for accessing arrays out of bounds?
  • Does this differ between literals and expressions? For instance, the compiler yields a warning if I write z(0).

This question is not about zero-sized arrays. I understand they are acceptable.

I think the answers to both of your questions are “no”. Btw,
gfortran -fbounds-check xcheck_bounds.f90 for

program main
  implicit none
  integer :: z(2)
  z = [ 1, 2 ]
  print*,z(sum(z)) ! out-of-bounds detected at run time
  print*,z(3) ! out-of-bounds detected at compile time
end program main

says

xcheck_bounds.f90:6:11:

    6 |   print*,z(3) ! out-of-bounds detected at compile time
      |           1
Warning: Array reference at (1) is out of bounds (3 > 2) in dimension 1

at compile time and gives at run time

At line 5 of file xcheck_bounds.f90
Fortran runtime error: Index '3' of dimension 1 of array 'z' above upper bound of 2
1 Like

Out of bound access to an array is an undefined behavior (it can return apparently valid values, or garbage, or crash, or whatever…). The standard does not require the compilers to check for them, and for performance reasons the compilers do not check them at runtime by default.

Accessing V(0) if the lower bound of V is 1 can be considered as a bug… Except maybe in in the case of an equivalence statement:

real :: u(10), v(10)
equivalence (u(5),v(1))

In this case, maybe v(0) is fully equivalent to u(4) (in practice it will be, but I’m not sure what the standard says about that).

1 Like

I don’t think it is standard-conforming, but for an array declared as

real :: x(2)

it could be that x(0) is passed to a procedure as an address one to the left of x(1).

For example, the program

subroutine print_vec(n, nskip, x)
implicit none
integer, intent(in) :: n, nskip
real, intent(in) :: x(n)
integer :: i
do i=max(1,nskip+1),n
   print*,i,x(i)
end do
print*
end subroutine print_vec

program main
implicit none
integer, parameter :: n = 2
real :: x(n)
x = [10, 20]
call print_vec(n, 0, x)
call print_vec(n, 0, x(1))
call print_vec(n, 1, x(0))
call print_vec(n, 0, x(0))
end program main

compiled with gfortran default options gives

           1   10.0000000    
           2   20.0000000    

           1   10.0000000    
           2   20.0000000    

           2   10.0000000    

           1   3.92363570E-43 (random junk)
           2   10.0000000