I am refactoring a F77 code for solving a system of second order PDEs along with coupled ODEs (if any). While testing, I encountered an aliasing bug that goes unnoticed even when warning and instrumentation flags are turned on.
Assume the global vector of unknowns is stored in an array U(NEQN)
where
NEQN = NPDE*NPTS + NV
, andNPDE
is the number of PDE variablesNPTS
is the number of grid points for the PDE semi-discretizationNV
is the number of ODE variables (a non-negative number)- the elements
U(1:NPDE*NPTS)
contain the values of the semi-discretized PDE variables - the elements
U(NPDE*NPTS+1:NEQN)
contain the values of the ODE variables
Deep in the solver, a procedure CSET
is invoked as follows
NVST = NPDE*NPTS + 1
C ... omitted
IV = NPDE*NPTS
IF (NV.GT.0) THEN
IV = NVST
C ... omitted
END IF
CALL CSET(NPDE,NPTS,U,WK(I6),WK,WK(I2),WK(I5),NEL,NPTL,WK(I4),
* WK(I12),XBK,IBK,WK(I3),U(IV),NV)
The procedure CSET
is defined as follows:
SUBROUTINE CSET(NPDE,NPTS,U,X,OMEGA,DU,XBK,NEL,NPTL,XC,CCR,XBH,
* IBK,DUTEM,V,NV)
C .. Scalar Arguments ..
INTEGER IBK, NEL, NPDE, NPTL, NPTS, NV
C .. Array Arguments ..
DOUBLE PRECISION CCR(NPTL), DU(NPTL,NPTL), DUTEM(NPTL,NPTL),
* OMEGA(NPTL,NPTL), U(NPDE,NPTS), V(1), X(NPTS),
* XBH(IBK), XBK(IBK), XC(NPTL)
Within CSET
, the PDE variables are associated to dummy argument U(NPDE,NPTS)
for 2-d indexing convenience. The ODE variables are passed via the penultimate argument, declared as V(1)
, and are associated to the actual argument U(IV)
.
(In codes of this era, it was common to declare an array as length 1, even if the actual array argument was longer. I never understood why programmers didn’t always use the assumed-size (*)
syntax in these cases. Was this just a bad habit?)
I spotted two unwanted issues here:
- The dummy argument
V(1)
should be declared either asV(*)
orV(NV)
. - Due to how
IV
is assigned, whenNV = 0
, there will be aliasing ofV(1)
with the elementU(NPDE,NPTS)
.
I’d like to amend this code in way which allows automatic bound-checking by changing the dummy argument declaration to
DOUBLE PRECISION ..., V(NV), ...
However to get rid of the aliasing for the NV = 0
case I will also need to modify the calling code to pass a dummy variable as actual argument:
DOUBLE PRECISION VDUM(1)
C ...
IF (NV > 0) THEN
CALL CSET(...,U(IV),NV)
ELSE
CALL CSET(...,VDUM,NV)
END IF
Does this sound like the correct approach to fix both issues?
This also made me wonder, what (if anything) did Fortran 77 say about array dummy arguments, when the size is zero? Would it be legal to reference an array of length-zero in any kind of context? Obviously, there is not much one can do with such an array.
subroutine zerolen(nv,v)
integer nv
double precision v(nv)
print *, nv
if (nv > 0) print *, v
end
C main program
external zerolen
double precision v(5)
nv = 0
call zerolen(nv,v) ! is nv = 0 allowed?
end