Technical data
Debugging Parallel Fortran
113
Multiprocess Debugging Session
This section takes you through the process of debugging the following
incorrectly multiprocessed code.
SUBROUTINE TOTAL(N, M, IOLD, INEW)
IMPLICIT NONE
INTEGER N, M
INTEGER IOLD(N,M), INEW(N,M)
DOUBLE PRECISION AGGREGATE(100, 100)
COMMON /WORK/ AGGREGATE
INTEGER I, J, NUM, II, JJ
DOUBLE PRECISION TMP
C$DOACROSS LOCAL(I,II,J,JJ,NUM)
DO J = 2, M–1
DO I = 2, N–1
NUM = 1
IF (IOLD(I,J) .EQ. 0) THEN
INEW(I,J) = 1
ELSE
NUM = IOLD(I–1,J) + IOLD(I,J–1) + IOLD(I–1,J–1) +
& IOLD(I+1,J) + IOLD(I,J+1) + IOLD(I+1,J+1)
IF (NUM .GE. 2) THEN
INEW(I,J) = IOLD(I,J) + 1
ELSE
INEW(I,J) = MAX(IOLD(I,J)–1, 0)
END IF
END IF
II = I/10 + 1
JJ = J/10 + 1
AGGREGATE(II,JJ) = AGGREGATE(II,JJ) + INEW(I,J)
END DO
END DO
RETURN
END
In the program, the LOCAL variables are properly declared. INEW always
appears with J as its second index, so it can be a SHARE variable when
multiprocessing the J loop. The IOLD, M, and N are only read (not written),
so they are safe. The problem is with AGGREGATE. The person analyzing










