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 
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
!..................................................................