Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
29277 Discussions

Dereference of pointer with allocatable arrays

salbruce
Beginner
947 Views

In converting a CVF fortran project to IVF I am getting strange numerical results. Trying to track down the problem I turned on some diagnostics, in particular,

Level of Source Code Analysis Only Critical Errors (/Qdiag-enable:sc1)

It gives the following errors
error #12172: dereference of pointer "IDEN" which is possibly equal to NULL set at...
error #12172: dereference of pointer "WORK" which is possibly equal to NULL set at...
The errors point to the lines
IDEN(I)=I ! initialize ranks
and
WORK(I)=S(L)
in the following subroutine.
IDEN and WORK are allocatable arrays that appear to be allocated with length N, whenever I call this subroutine. Can someone help interpret these messages?
Thanks.
------------------
SUBROUTINE RANKSIMPLE(S,IDEN,WORK,N,IND)
! Ranks S, of N elements, into ascending or descending order.
! IDEN is the same dimension as S and on exit holds the
! rank of each of the original elements S.
! E.g., with IND=1, S(1) ends up as the smallest value and IDEN(1) tells its
! original position in S.
! WORK is a real array used for workspace, of same dimension as S
! IF IND = 1, S IS SORTED IN ASCENDING ORDER.
! IF IND = -1, S IS SORTED IN DESCENDING ORDER.

DIMENSION S(N), IDEN(N), WORK(N)
XIND=FLOAT(IND)
IF (IND.LE.0) THEN ! Reverse sign for descending order
DO I=1,N
S(I)=-S(I)
END DO
ENDIF
DO I=1,N
IDEN(I)=I ! initialize ranks
END DO

M=N
2 M=INT(FLOAT(M)/2.)
IF (M.EQ.0) GOTO 8
K=N-M
J=1
4 I=J
5 IM=I+M
L=IDEN(I)
LM=IDEN(IM)
IF (S(L)-S(LM).GE.0.) 7,7,6
6 IDEN(I)=LM
IDEN(IM)=L
I=I-M
IF(I-1) 7,5,5
7 J=J+1
IF(J-K) 4,4,2

8 DO I=1,N ! finish up by sorting WORK by IDEN
L=IDEN(I)
WORK(I)=S(L)
END DO
! then copying WORK back into the original array
IF (IND.LE.0) THEN ! descending order
DO I=1,N
S(I)=-WORK(I)
END DO
ELSE ! ascending order
DO I=1,N
S(I)=WORK(I)
END DO
ENDIF

RETURN
END
0 Kudos
1 Solution
Steven_L_Intel1
Employee
947 Views

Unfortunately, the Source Checker feature is fairly ignorant when it comes to Fortran code. What you have shown here has neither POINTER nor ALLOCATABLE arrays. IDEN and WORK are ordinary "adjustable arrays", a Fortran 77 feature. It's possible that Source Checker sees something wrong with the caller of this routine, but you haven't shown that. I'm more likely to suggest that the Source Checker diagnostics here should be ignored.

Generally, when I have a program with "strange numerical results", I start digging into where the results are computed and compare the "strange" results of intermediate calculations with what I think is correct, looking for the point of divergence. I will comment that it's not at all unusual to have floating point differences between CVF and IVF due to IVF's use of SSE registers and more advanced optimizations. If the answers are VERY different, then perhaps there's a program bug (or possibly a compiler bug). You'll have to compare the two programs to see where things change.

View solution in original post

0 Kudos
4 Replies
Steven_L_Intel1
Employee
948 Views

Unfortunately, the Source Checker feature is fairly ignorant when it comes to Fortran code. What you have shown here has neither POINTER nor ALLOCATABLE arrays. IDEN and WORK are ordinary "adjustable arrays", a Fortran 77 feature. It's possible that Source Checker sees something wrong with the caller of this routine, but you haven't shown that. I'm more likely to suggest that the Source Checker diagnostics here should be ignored.

Generally, when I have a program with "strange numerical results", I start digging into where the results are computed and compare the "strange" results of intermediate calculations with what I think is correct, looking for the point of divergence. I will comment that it's not at all unusual to have floating point differences between CVF and IVF due to IVF's use of SSE registers and more advanced optimizations. If the answers are VERY different, then perhaps there's a program bug (or possibly a compiler bug). You'll have to compare the two programs to see where things change.
0 Kudos
salbruce
Beginner
947 Views

Unfortunately, the Source Checker feature is fairly ignorant when it comes to Fortran code. What you have shown here has neither POINTER nor ALLOCATABLE arrays. IDEN and WORK are ordinary "adjustable arrays", a Fortran 77 feature. It's possible that Source Checker sees something wrong with the caller of this routine, but you haven't shown that. I'm more likely to suggest that the Source Checker diagnostics here should be ignored.

Generally, when I have a program with "strange numerical results", I start digging into where the results are computed and compare the "strange" results of intermediate calculations with what I think is correct, looking for the point of divergence. I will comment that it's not at all unusual to have floating point differences between CVF and IVF due to IVF's use of SSE registers and more advanced optimizations. If the answers are VERY different, then perhaps there's a program bug (or possibly a compiler bug). You'll have to compare the two programs to see where things change.

0 Kudos
salbruce
Beginner
947 Views
Thanks for the suggestions. The results are WAY off, so yes I will need to step through this. I had thought that there might be some difference in how forgiving the two compilers were, so I thought I would see if IVF diagnostics would help point to the problem.

In this case, I am allocating those arrays in the main program and passing them to the subroutine that I listed. For example, from the calling program:

[cpp]      DIMENSION WORK   [ALLOCATABLE] (:)
[/cpp]
(snip)
[cpp]         ALLOCATE (X1(NST,NAXES),X2(NST,NAXES),X3(NST,NAXES), ! get more memory
     +    DIST(NDIM2),STR(NSIZE),GCHAR(NSIZE),WORK(NDIM2),
     +    WORK2(MAXIT),IJ(NDIM2),DHAT(NDIM2),IWORK(NDIM2),
     +    IWORK2(MAXIT),STAT=IERR)
[/cpp]

I'll ignore the diagnostics as you suggest. Just hoping for clues there. Is it possible that it is confused by my initializing these arrays in a subroutine rather than the main program where they were allocated?

I'm also puzzled about the diagnostic for some of my OPEN statements, such as:

OPEN (UNIT=IUNIT,FILE=FNAME,STATUS='UNKNOWN',IOSTAT=IERR)
which gives this diagnostic:
warning #12331: function "open" is vulnerable to race conditions

Is there a better OPEN statement that I should be using?

Thanks again.
-Bruce

--------
Unfortunately, the Source Checker feature is fairly ignorant when it comes to Fortran code. What you have shown here has neither POINTER nor ALLOCATABLE arrays. IDEN and WORK are ordinary "adjustable arrays", a Fortran 77 feature. It's possible that Source Checker sees something wrong with the caller of this routine, but you haven't shown that. I'm more likely to suggest that the Source Checker diagnostics here should be ignored.

Generally, when I have a program with "strange numerical results", I start digging into where the results are computed and compare the "strange" results of intermediate calculations with what I think is correct, looking for the point of divergence. I will comment that it's not at all unusual to have floating point differences between CVF and IVF due to IVF's use of SSE registers and more advanced optimizations. If the answers are VERY different, then perhaps there's a program bug (or possibly a compiler bug). You'll have to compare the two programs to see where things change.

0 Kudos
Steven_L_Intel1
Employee
947 Views
Ignore the source checker diagnostic about "open". It's wrong.
0 Kudos
Reply