Compiler option to warn about argument declarations of x(1) instead of x(*)

In old Fortran code such as the IBM 360 Scientific Subroutine Package an array argument was sometimes declared to have upper bound of 1 with x(1), when x(*) was actually intended. I think that has never been standard but has been widely accepted. Are there compilers with options that will warn about this at compile time or cause the program to fail at run-time if x(i) with i > 1 is accessed? All of

gfortran -std=f2018 -Wall -Wextra
ifx /nologo /stand:f18 /warn:all
g95 -std=f95 -Wall -Wextra

compile and run

module m
implicit none
contains
real function mysum(n, x)
! sum the values x(1:n)
implicit none
integer n
real x(1)
integer :: i
mysum = 0.0
do i=1,n
   mysum = mysum + x(i)
end do
end function mysum
end module m

program main
use m, only: mysum
implicit none
integer, parameter :: n = 3
real :: x(n)
x = [10, 20, 30]
print*,mysum(n, x)
end program main

without warning about real x(1) and all give output of 60.0000000.

I tweeted about this, and someone asked about compiler options to detect this usage.

1 Like

This can be detected with bounds checkings:

HPE Cray Fortran also has a bounds-checking option, but it is disabled in the x(1) case:

-h [no]bounds Enable or disable checking of array bounds. Bounds checking is not performed on arrays dimensioned as (1). Enables -h overindex . Equivalent to the -Rb option.


I’ve tested the options in Compiler Explorer: Compiler Explorer. For some reason, ifort and ifx don’t trigger the test I made. Edit: just confirmed it works for nagfor:

> nagfor -C=array bounds.f90 
NAG Fortran Compiler Release 7.2(Shin-Urayasu) Build 7203
[NAG Fortran Compiler normal termination]
> ./a.out
Runtime Error: bounds.f90, line 4: Subscript 1 of X (value 5) is out of range (1:1)
4 Likes

Yeah - this special case in the Intel compiler can’t be disabled.

3 Likes

Thanks for the explanation. So in the example,

subroutine check(x,i)
real, intent(inout) :: x(2)    ! with ifx and ftn (HPE Cray) bounds only checked when n > 1
integer :: i
x(i) = 42
end subroutine

program test
external :: check
real :: x(3)
call check(x,5)
end program

the check is triggered,

forrtl: severe (408): fort: (2): Subscript #1 of the array X has value 5 which is greater than the upper bound of 2

2 Likes

Perhaps worth adding here, with assumed-size arrays like x(*), bounds-checking typically can’t be done (or at least not along the ultimate dimension). So providing the expected size is a best practice worth following IMO.

The x(*) syntax was introduced in f77, so early fortran for the first 20 years before that relied on the de facto x(1) convention to specify an array of unknown/arbitrary/unspecified length. The IBM library was developed in the 1960s, during that time.

nagfor’s -C=calls will check assumed-size arrays for bounds violations on all dimensions. Both the call site and the subprogram need to be compiled with -C=calls.

2 Likes

Thanks for the clarification. Has it always been valid to declare an argument as x(n), where n is a procedure argument? If so, why did many of the pre-Fortran-77 programmers not do that?

Fortran 66 called these “adjustable arrays”. https://archive.org/details/ansi-x-3.9-1966-fortran-66

If the actual mathematical object being worked on is a triangular matrix (or other special matrix form) the actual sorage size of the object would be different from the number of rows/columns, and require an additional argument to the subroutine. The numeric value in the declarator subscript statement could be a literal integer:

dimension x(10,10)

or a variable:

dimension x(N,N),

but not an expression.

dimension x(N*N/2+1)

This practice avoids that and was (still is) 100% portable.

1 Like

As noted above, there are many situations where the array size is determined elsewhere, but the computational parameters are available as an argument, or in a common block, etc. Think of structured matrices (triangular, strictly lower triangular, tridiagonal, banded, subblocked, various sparse formats, and so on). Since there was no way to specify these simply within the language at that time, the x(1) convention was used, replaced by the x(*) syntax in f77, which simply says that this is a dummy array of unspecified size and it is the programmer’s responsibility to address the actual elements correctly. This is similar to other languages such as C in which arrays are specified simply by the address of the first element; in fact, in C an array reference is just another way to specify pointer arithmetic.

I might also add to this discussion that early compilers were sometimes not very efficient with multidimensional array addressing. Many programmers thought that they could write the indexing expressions more efficiently than could the compiler, so they used the x(1) convention to pass in the address of the dummy array, and then did the multidimensional indexing within that workspace manually.

2 Likes

That makes more sense now. I’ve asked myself the same question as @Beliavsky before, when I was fixing the issue in the thread:

Nowadays expressions are allowed:

subroutine demo1(n,x)
    integer :: n
    real :: x(n*n/2)
    print *,x
end subroutine

subroutine demo2(x,ipar)
    integer :: ipar(7)
    real :: x((ipar(1)**2)/2)
    print *, x
end subroutine

and an array is allowed to have zero-length which clashes with the (non-standard) v(1) convention.

F66 was often quite limited in where expressions could occur and how complicated they could be. F77 allowed them in more places. And especially with array subscripts, how complicated they could be. It is why in very old code one sometimes sees an array subscript being computed and assigned to a temporary variable - then used later as a subscript. Whereas in F77 you could directly code the subscript expression. (Though it was a common F66 extension to allow more expressions in more places.)

I don’t understand why v(1) would be considered zero-length, or why it would be problematic, if indeed there was exactly one element. It seems like a unit length array to me. In the code I am now working on I have statements like this:

parameter(last=2024)
dimension x(2024:last)

because I intend to update the code next year. I never gave a thought to its possible invalidity. Is it non-standard? Does not being a literal “1” excuse it? GNU doesn’t complain even with diagnostics turned way up.

Nice that expressions are now allowed. That sort of orthogonality isn’t costly and is appreciated.

The problem is when the actual argument is a zero-length array, and the dummy argument is an array of length 1. That is not allowed, although it usually has no consequences when the dummy array is not referenced.

1 Like

My reply was a bit vague. What I was trying to say was the x(1) convention for dummy arguments doesn’t permit correctly capturing zero-length arrays:

module m
implicit none
contains
subroutine demo0(n,x)
    integer :: n
    real :: x(n)
    print *, size(x)
end subroutine

subroutine demo1(n,x)
    integer :: n
    real :: x(1)        ! legacy convention, actual argument of length n
    print *, size(x)
    x(1) = 3.0          ! <- potentially a logical error
end subroutine
end module

program test
use m
real :: x(1)
call demo0(size(x(1:0)), x(1:0))   ! 0
call demo1(size(x(1:0)), x(1:0))   ! 1
end program

Edit: the x(1) convention also returns a false size() value,

subroutine check(n,a)
    real :: a(1)               ! actual argument is supposed to be >= 3*n
    print *, size(a)
end subroutine

With the F77-introduced assumed-size syntax, you get an error at least:

subroutine check(n,a)
    real :: a(*)       ! actual argument is supposed to be >= 3*n
    print *, size(a)   ! Error: The upper bound in the last dimension must appear 
                       !        in the reference to the assumed size array 'a' at (1)
end subroutine

x(1) and x(*) comes up in practically every attempt to modernize an older FORTRAN code.
And it can be the biggest issue in salvaging old code as there is still no good equivalent that is standard. Every HPC compiler I used supported it. It not only indicated an arbitrary number of elements but an arbitrary number of dimensions. It could be considered equivalent to an address to the beginning of an arbitrary number of contiguous values. Note that FORTRAN originated with IBM so the fact that the library mentioned above uses it that way pretty much seals the deal that was expected behavior. I just took the first procedure (alphabetically) in that collection and used it to show a plausible evolution of the routine from FORTRAN 66 to modern Fortran, I was very surprised without taking too many liberties I could get the versions to compile in a single file. The gfortran compiler at least let me still pass a matrix to the vector. It may or may not be clobbering memory but it runs. I was going to look at the intermediate code to see if that was a fluke or really supported. It might be amusing to see how the routine could have progressed through the years. I think it at first gets easier to read and more intuitive for a non-programmer STEM but then starts to accumulate more programmer-centric features than algorithmic features, like Fortran :wink:

ABSNT
!NAME   
!   ABSNT
!SYNOPSIS
!      CALL ABSNT (A,S,NO,NV)
!PURPOSE
!      Test for "missing" or zero values for each "observation"
!      or row in matrix A.
!OPTIONS
!      A  - Observation matrix, NO by NV
!      S  - Output vector of length NO indicating the following
!           codes for each observation.
!           1  There is not a "missing" (ie. zero) value.
!           0  At least one value is "missing" or zero.
!      NO - Number of observations. NO must be > or = to 1.
!      NV - Number of variables for each observation. NV must be
!           greater than or equal to 1.
!REMARKS
!      None
!SUBROUTINES AND FUNCTION SUBPROGRAMS REQUIRED
!      None
!METHOD
!      A test is made for each row (observation) of the matrix A.
!      If there is not a missing (ie. zero) value, 1 is placed in
!      S(J). If at least one value is zero, 0 is placed
!      in S(J).
!..................................................................
! ORIGINAL: note dimensioned to "1" not "*", and 
!           array type mismatch as A is a vector
      SUBROUTINE ABSNT_0(A,S,NO,NV)    
      DIMENSION A(1),S(1)     
      DO 20 J=1,NO                
      IJ=J-NO                    
      S(J)=1.0                  
      DO 10 I=1,NV             
      IJ=IJ+NO                
      IF(A(IJ)) 10,5,10      
    5 S(J)=0                
      GO TO 20             
   10 CONTINUE            
   20 CONTINUE           
      RETURN            
      END              
!..................................................................
      SUBROUTINE ABSNT_00(A,S,NO,NV)    
      DIMENSION A(1),S(1)     
      DO J=1,NO                
         IJ=J-NO                    
         S(J)=1.0                  
         DO I=1,NV             
            IJ=IJ+NO                
            IF(A(IJ).eq.0) THEN
               S(J)=0                
               GOTO 999
            ENDIF
         ENDDO               
999      CONTINUE
      ENDDO              
      RETURN            
      END              
!..................................................................
! do/enddo, if/endif instead of computed goto, implicit none, ...
subroutine absnt_000(a,s,no,nv)
implicit none
integer,intent(in) :: no, nv
real,intent(in)    :: a(no,nv)
real,intent(out)   :: s(no)
integer            :: i, j
   do j = 1, no
      s(j) = 1.0
      do i = 1, nv
         if ( a(j,i) == 0 ) then
            s(j) = 0
            exit
         endif
      enddo
   enddo 
end subroutine absnt_000
!..................................................................
! change to array syntax and intrinsics
subroutine absnt_0000(a,s,no,nv)
implicit none
integer,intent(in) :: no, nv
real,intent(in)    :: a(no,nv)
real,intent(out)   :: s(no)
integer            :: j
   do j = 1, no
      s(j) = merge( 0.0, 1.0, any( a(j,:) == 0 ) )
   enddo 
end subroutine absnt_0000
!..................................................................
subroutine absnt(a,s,no,nv)
implicit none
integer,intent(in) :: no, nv
real,intent(in)    :: a(no,nv)
real,intent(out)   :: s(no)
   s = merge( 1.0, 0.0, count(a == 0,2) == 0 )
end subroutine absnt
!..................................................................
! a module, probably would make it generic or metamorphic
! and change interface at some point. Changed to a function
! and eliminated passing size and change return type to integer
module m_ibm
implicit none
private
integer,parameter :: dp=kind(0.0d0)
interface absnt
   module procedure absnt_e
   module procedure absnt_d
end interface absnt
public absnt
contains

pure function absnt_e(a) result(s)
real,intent(in)          :: a(:,:) 
integer                  :: s(size(a,dim=1)) 
   s = merge( 1, 0, count(a == 0,2) == 0 )
end function absnt_e

pure function absnt_d(a) result(s)
real(kind=dp),intent(in) :: a(:,:) 
integer                  :: s(size(a,dim=1)) 
   ! different method for no reason
   s = abs(min(count(a == 0,2), 1) -1)
end function absnt_d

end module m_ibm
!..................................................................
!program test_absnt

!end program test_absnt
!..................................................................
program demo_absnt
use M_ibm, only : absnt_ibm=> absnt
integer, parameter :: no=5, nv=7
real,parameter :: arr(no,nv)= reshape([& ! define array in row-column order
    !=================================!
   & 1.0, 2.0, 3.0, 4.0, 5.0, 6.0, 7.0, &   ! set 1
   & 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 7.0, &   ! set 2
   & 1.0, 2.0, 3.0, 4.0, 5.0, 6.0, 7.0, &   ! set 3
   & 1.0, 2.0, 3.0, 4.0, 5.0, 6.0, 7.0, &   ! set 4
   & 1.0, 2.0, 3.0, 0.0, 5.0, 6.0, 7.0  &   ! set 5
    !=================================!
],shape(arr),order=[2,1])
external absnt_0, absnt_00, absnt_000, absnt_0000, absnt
   call printit(absnt_0)
   call printit(absnt_00)
   call printit(absnt_000)
   call printit(absnt_0000)
   call printit(absnt)
   write(*,'(*(g0,1x))')absnt_ibm(arr),'|',absnt_ibm(transpose(arr))
contains
subroutine printit(func)
real :: s(no)
real :: t(nv)
external func
   call func (arr,s,no,nv)
   write(*,'(*(g0,1x))',advance='no')nint(s),'|'
   call func (transpose(arr),t,nv,no)
   write(*,'(*(g0,1x))')nint(t)
end subroutine printit
end program demo_absnt
!..................................................................
4 Likes

If n can be zero, it’s up to the developer of demo1 to protect references to x

    if (n>0) x(1) = 3.0          ! <- no more error
1 Like

What’s the best way of statically diagnosing this? I guess dimension(1) is (almost?) always a code smell, as the programmer presumably either meant it to be a scalar or this “adjustable array”, so one could always warn on dummy arguments with size exactly 1. Slightly more involved would be to check if the array is indexed with anything other than a literal 1.

Are there any genuinely useful cases where dimension(1) is actually intended? It can’t be used for overload resolution, so could it always be safely replaced with dimension(:)?

It not only indicated an arbitrary number of elements but an arbitrary number of dimensions.

@urbanjost In the absnt example, A is still indexed as rank-1, just using a flattened index. Do you mean that they could also be indexed as rank-2 or more? If they were still required to be indexed as rank-1, can they not be replaced with assumed-shape, dimension(:)?

I think Urbanjost is referring to the fact that the array received as a(1) can be passed on to another subroutine where it is dimensioned a(n,n), provided the original array was of sufficient size. This was frequently used to emulate dynamic memory. It would not be useful to eliminate this ability merely to satisfy animosity to old ways.