Fixing FORTRAN IV warning: “The number of arguments is incompatible with intrinsinc procedure, assume 'external' ”

南笙酒味 提交于 2019-12-02 21:00:41

问题


I need to run an old FORTRAN IV code I was given (which is supposed to run just fine). I downloaded a trial version of Intel compiler and tried to compile the source file I was given with the command:

ifort  -f66 abel.for -o mycode

where abel.for is the name of the source file. I got a bunch of warnings and errors. I wanted to ask about the first warning I was given:

The number of arguments is incompatible with intrinsinc procedure, assume 'external'.  [KNOT]

where KNOT is a function defined as:

C                                                                       AAOK0162
C  PROCEDURE FOR LOCATING THE SPLINE SECTION TO WHICH AN                AAOK0163
C  ARGUMENT BELONGS.                                                    AAOK0164
C        N    NUMBER OF KNOTS IN THE SPLINE REPRESENTATION              AAOK0165
C        U    KNOTS POSITION                                            AAOK0166
C        X    THE ARGUMENT WHOSE SPLINE SECTION IS SOUGHT               AAOK0167
C        I    THE NUMBER OF THE SMALLEST KNOT LARGER THAN X             AAOK0168
C                                                                       AAOK0169
      INTEGER FUNCTION KNOT(N,U,X)                                      AAOK0170
      IMPLICIT REAL*8(A-H,O-Z)                                          AAOK0171
      DIMENSION U(1)                                                    AAOK0172
C TEST WHETHER POINT IN RANGE                                           AAOK0173
      IF (X.LT.U(1)) GOTO 990                                           AAOK0174
      IF (X.GT.U(N)) GOTO 990                                           AAOK0175
C ESTIMATE KNOT INTERVAL BY ASSUMING EQUALLY SPACED KNOTS               AAOK0176
      J=DABS(X-U(1))/(U(N)-U(1))*(N-1)+1                                AAOK0177
C ENSURE CASE X=U(N) GIVES J=N-1                                        AAOK0178
      J=MIN0(J,N-1)                                                     AAOK0179
C SEARCH FOR KNOT INTERVAL CONTAINING X                                 AAOK0180
      IF (X.GE.U(J)) GOTO 11                                            AAOK0181
2     J=J-1                                                             AAOK0182
      IF(X.LT.U(J)) GOTO 2                                              AAOK0183
      GOTO 7                                                            AAOK0184
1     J=J+1                                                             AAOK0185
11    IF(X.GT.U(J+1)) GOTO 1                                            AAOK0186
7     KNOT=J+1                                                          AAOK0187
      RETURN                                                            AAOK0188
990   KNOT=-1                                                           AAOK0189
      RETURN                                                            AAOK0190
      END                                                               AAOK0191

and the compiler error indicates the call of this function from a subsequent subroutine (line AAOK0211):

      SUBROUTINE ABEL1(N,IN,X,XN,A,B,C,D,YCALC)                         AAOK0201
      IMPLICIT REAL*8 (A-H,O-Z)                                         AAOK0202
      DIMENSION X(1),XN(1),A(1),B(1),C(1),D(1),YCALC(1)                 AAOK0203
      COMMON /R/ R                                                      AAOK0204
      COMMON /PI/ PI                                                    AAOK0205
      DO 70 L=1,IN                                                      AAOK0206
      R=X(L)                                                            AAOK0207
      IF(R.EQ.0.D0) R=1.D-6                                             AAOK0208
      YCALC(L)=0.D0                                                     AAOK0209
      IF (R.EQ.XN(N+1)) R=R-1.D-6                                       AAOK0210
      I=KNOT(N+1,XN,R)                                                  AAOK0211
      IF(I.EQ.-1) GOTO 70                                               AAOK0212
      IF(I.EQ.N+1) GOTO 99                                              AAOK0213
      DO 60 K=I,N                                                       AAOK0214
      X1=XN(K)                                                          AAOK0215
      X2=XN(K+1)                                                        AAOK0216
      S=3.D0*A(K)*DI1(2,X1,X2)+2.D0*B(K)*DI1(1,X1,X2)+C(K)*DI1(0,X1,X2) AAOK0217
      YCALC(L)=YCALC(L)+S                                               AAOK0218
60    CONTINUE                                                          AAOK0219
99    X2=XN(I)                                                          AAOK0220
      S=3.D0*A(I-1)*DI1(2,R,X2)+2.D0*B(I-1)*DI1(1,R,X2)                 AAOK0221
     *       +C(I-1)*DI1(0,R,X2)                                        AAOK0222
      YCALC(L)=-(YCALC(L)+S)/PI                                         AAOK0223
70    CONTINUE                                                          AAOK0224
      RETURN                                                            AAOK0225
      END                                                               AAOK0226

I wanted to ask what seems to cause this warning and if it is safe to just ignore it?


回答1:


KNOT() is a non-standard specific intrinsic function for the NOT function which accepts 8 byte integers (see https://docs.oracle.com/cd/E19422-01/819-3684/3_F77_Intrins.html ).

You can indeed ignore the warning in this case. Because the numbers and types of the arguments differ, the compiler will not call the intrinsic inadvertently, so it is safe. The problem would be if the compiler had a function which looks exactly the same but does something different. The external statement serves the purpose to prevent such collisions.

The thing you can do to suppress the warning is to tell the compiler you have your own external function KNOT() by placing

EXTERNAL *KNOT

in the declaration section of each compilation unit which calls KNOT, so for example,

SUBROUTINE ABEL1(N,IN,X,XN,A,B,C,D,YCALC)
      IMPLICIT REAL*8 (A-H,O-Z)
      EXTERNAL *KNOT

The type should be all-right given your implicit typing rules, but you can specify it explicitly by

      INTEGER KNOT

Note: the * in EXTERNAL *KNOT means that not an intrinsic, but a user-supplied function should be used. This behaviour differs from modern Fortran! See http://h21007.www2.hp.com/portal/download/files/unprot/fortran/docs/lrm/lrm0633a.htm In FORTRAN 77 and later use just EXTERNAL KNOT.



来源:https://stackoverflow.com/questions/33012052/fixing-fortran-iv-warning-the-number-of-arguments-is-incompatible-with-intrins

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!