Paul, here is a shorter reproducer that also generates its own input data instead of reading a large input data file.
program gcgtst ! demonstrates bug(s) related to ASSOCIATE
implicit none
integer, parameter :: kdp = kind(0.0d0)
integer nrn, nbn, nxyz, i, j
real (kind=kdp), allocatable :: rhs(:), xx(:), w(:), rr(:), va(:, :)
integer, allocatable :: ci(:, :)
call getint(nrn) ! get integer in range 1-9999 from command line argument
nbn = nrn
nxyz = nrn+nbn
allocate (rhs(nxyz), xx(nxyz), va(7,nxyz), ci(6,nxyz), w(nbn), rr(nbn))
do i = 1, nxyz
xx(i) = real(i)/nxyz
va(:,i) = [(j*xx(i), j=1,7)]
end do
ci = 0
call gcgr()
contains
subroutine getint(n)
use iso_fortran_env
implicit none
integer, intent(out) :: n
character(len=4) :: str
character(len=1), parameter :: sl = '/'
if(command_argument_count() .eq. 1)then
call get_command_argument(1, str)
read (str,'(I4)')n
else
n = 80
endif
print '(a,A1,a,A1,4x,i5)', compiler_version(),sl, compiler_options(),sl,n
return
end subroutine getint
subroutine gcgr()
implicit none
integer nrnp1
nrnp1 = nrn + 1
associate (rhs_r => rhs(1:nrn), rhs_b => rhs(nrnp1:nxyz), & ! rhs_r and rhs_b never used again
xx_b => xx(nrnp1:nxyz)) ! undef. var. reported here!
rr = 0.0
call armult(w, rr) ! w is never used again; this call could be commented out, but that kills bug
call dbmult(rr, xx_b)
end associate
print '(1x,5ES12.4)', rr(1:min(5,nbn))
return
end subroutine gcgr
subroutine dbmult(x, y)
implicit none
real (kind=kdp), dimension (:), intent (out) :: x
real (kind=kdp), dimension (:), intent (in) :: y
integer :: i, j
do i = 1, nbn
j = i + nrn
x(i) = y(i)*va(7, j)
end do
end subroutine dbmult
subroutine armult(x, y)
implicit none
real (kind=kdp), dimension (:), intent (out) :: x
real (kind=kdp), dimension (:), intent (in) :: y
integer :: i, ii, j, jcol
real (kind=kdp) :: s
do i = 1, nbn
ii = i + nrn
s = 0.0_kdp
do j = 1, 6
jcol = ci(j, ii)
if (jcol>0) s = s + va(j, ii)*y(jcol) ! never executed since ci = 0
end do
x(i) = s ! when ci == 0, x(:) is set to 0
end do
end subroutine armult
end program
[post limit reached, continued in next post]