Compiling Burkardt's SLATEC with gfortran

In the thread About a Fortran Scientific Library, SLATEC was mentioned as a notable Fortran library. John Burkardt has modernized many Fortran 77 codes, including SLATEC, for one thing moving them to free source form. I can compile and run his version of SLATEC with g95, but compiling with gfortran -c -w slatec.f90 I get many errors, starting with

slatec.f90:218116:33:

218116 |       DATA RMACH(5) / Z'3E9A209B' /
       |                                 1
Error: BOZ literal constant near (1) cannot be assigned to a REAL variable [see '-fno-allow-invalid-boz']
slatec.f90:218115:33:

If we can get SLATEC to compile cleanly with gfortran, that would be a step towards a modern Fortran scientific library. Is there a gfortran compiler option I should used?

1 Like

Compiling with gfortran -c -w -fallow-invalid-boz still gives many errors:

slatec.f90:221350:0:

150867 | COMMON /DDEBD1/ ROWND,CONIT,CRATE,EL(13),ELCO(13,12),HOLD,RC,RMAX, &
| 2

221350 | FUNCTION RC (X, Y, IER)
|
Error: Global entity ‘rc’ at (1) cannot appear in a COMMON block at (2)
slatec.f90:221350:0: Error: (1)
slatec.f90:277754:17: Error: Global entity ‘rc’ at (1) cannot appear in a COMMON block at (2)
slatec.f90:249654:58:

249654 | call CHKDER(M,N,X,FVEC,FJAC,LDFJAC,WA1,WA4,MODECH,ERR)
| 1
Error: Rank mismatch in argument ‘err’ at (1) (rank-1 and scalar)
slatec.f90:249665:30:

249665 | WA4(I),MODECH,ERR)
| 1
Error: Rank mismatch in argument ‘err’ at (1) (rank-1 and scalar)
slatec.f90:249736:58:

249736 | call CHKDER(M,N,X,FVEC,FJAC,LDFJAC,WA1,WA4,MODECH,ERR)
| 1
Error: Rank mismatch in argument ‘err’ at (1) (rank-1 and scalar)
slatec.f90:249750:58:

249750 | call CHKDER(1,N,X,FVEC(I),WA3,1,WA1,WA4(I),MODECH,ERR)
| 1
Error: Rank mismatch in argument ‘err’ at (1) (rank-1 and scalar)
slatec.f90:230624:19:

230624 | call SCOPY(NCOLS,ZERO,0,X,1)
| 1
Error: Rank mismatch in argument ‘sx’ at (1) (rank-1 and scalar)
slatec.f90:230693:19:

230693 | call SCOPY(NCOLS,ZERO,0,WW,1)
| 1
Error: Rank mismatch in argument ‘sx’ at (1) (rank-1 and scalar)
slatec.f90:230758:23:

230758 | call IVOUT(0,I,’(’’ FOUND NO VARIABLE TO ENTER’’)’,-4)
| 1
Error: Rank mismatch in argument ‘ix’ at (1) (rank-1 and scalar)
slatec.f90:230767:19:

230767 | call IVOUT(1,JBIG,’(’’ TRY TO BRING IN THIS COL.’’)’,-4)
| 1
Error: Rank mismatch in argument ‘ix’ at (1) (rank-1 and scalar)
slatec.f90:230788:23:

230788 | call IVOUT(0,I,’(’’ VARIABLE IS DEPENDENT, NOT USED.’’)’, &
| 1
Error: Rank mismatch in argument ‘ix’ at (1) (rank-1 and scalar)
slatec.f90:230828:23:

230828 | call IVOUT(0,I,’(’’ PIVOT IS ZERO, NOT USED.’’)’,-4)
| 1
Error: Rank mismatch in argument ‘ix’ at (1) (rank-1 and scalar)
slatec.f90:230852:19:

230852 | call IVOUT(0,I,’(’’ VARIABLE HAS BAD DIRECTION, NOT USED.’’)’, &
| 1
Error: Rank mismatch in argument ‘ix’ at (1) (rank-1 and scalar)
slatec.f90:231075:19:

231075 | call SCOPY(NCOLS,ZERO,0,X,1)
| 1
Error: Rank mismatch in argument ‘sx’ at (1) (rank-1 and scalar)
slatec.f90:42974:39:

42974 | call CPEVL(N,0,T(N1),CMPLX(X,0.0),PN,PN,.FALSE.)
| 1
Error: Rank mismatch in argument ‘c’ at (1) (rank-1 and scalar)
slatec.f90:42979:39:

42979 | call CPEVL(N,0,T(N1),CMPLX(X,0.0),PN,PN,.FALSE.)
| 1
Error: Rank mismatch in argument ‘c’ at (1) (rank-1 and scalar)
slatec.f90:42994:33:

42994 | call CPEVL(N,0,A,R(I),PN,TEMP,.TRUE.)
| 1
Error: Rank mismatch in argument ‘c’ at (1) (rank-1 and scalar)
slatec.f90:194400:33:

194400 | call CSCALE(A,NRDA,M,N,COLS,CS,DUM,DUM,ANORM,SCALES,ISCALE,0)
| 1
Error: Rank mismatch in argument ‘rows’ at (1) (rank-1 and scalar)
slatec.f90:224452:49:

224452 | call RFFTB1 (N,R,WSAVE,WSAVE(N+1),WSAVE(2*N+1))
| 1
Error: Type mismatch in argument ‘ifac’ at (1); passed REAL(4) to INTEGER(4)
slatec.f90:224690:49:

224690 | call RFFTF1 (N,R,WSAVE,WSAVE(N+1),WSAVE(2*N+1))
| 1
Error: Type mismatch in argument ‘ifac’ at (1); passed REAL(4) to INTEGER(4)
slatec.f90:224895:41:

224895 | call RFFTI1 (N,WSAVE(N+1),WSAVE(2*N+1))
| 1
Error: Type mismatch in argument ‘ifac’ at (1); passed REAL(4) to INTEGER(4)
slatec.f90:166931:20:

166931 | call SSORT (BKPT, DUMMY, NBKPT, 1)
| 1
Error: Rank mismatch in argument ‘y’ at (1) (rank-1 and scalar)
slatec.f90:167087:25:

167087 | call SCOPY (NORDP1, 0.E0, 0, G(IR,1), MDG)
| 1
Error: Rank mismatch in argument ‘sx’ at (1) (rank-1 and scalar)
slatec.f90:167141:25:

167141 | call SCOPY (NP1, 0.E0, 0, W(NEQCON,1), MDW)
| 1
Error: Rank mismatch in argument ‘sx’ at (1) (rank-1 and scalar)
slatec.f90:167166:20:

167166 | call SCOPY (N, 0.E0, 0, W(IROW,1), MDW)
| 1
Error: Rank mismatch in argument ‘sx’ at (1) (rank-1 and scalar)
slatec.f90:167190:23:

167190 | call SCOPY (N, 0.E0, 0, W(IROW,1), MDW)
| 1
Error: Rank mismatch in argument ‘sx’ at (1) (rank-1 and scalar)
slatec.f90:189986:17:

189986 | call SCOPY (N, 1.E0, 0, WS(N1), 1)
| 1
Error: Rank mismatch in argument ‘sx’ at (1) (rank-1 and scalar)
slatec.f90:190138:30:

190138 | call SCOPY (N-KRANKE, 0.E0, 0, W(I,KRANKE+1), MDW)
| 1
Error: Rank mismatch in argument ‘sx’ at (1) (rank-1 and scalar)
slatec.f90:190362:17:

190362 | call SCOPY (N, 0.E0, 0, WS, 1)
| 1
Error: Rank mismatch in argument ‘sx’ at (1) (rank-1 and scalar)
slatec.f90:190368:51:

190368 | call HFTI (W, MDW, MA, N, WS, MA, 1, TAU, KRANK, RNORM, WS(N2), &
| 1
Error: Rank mismatch in argument ‘rnorm’ at (1) (rank-1 and scalar)
slatec.f90:190501:23:

190501 | call SCOPY (I, 0.E0, 0, W(I,1), MDW)
| 1
Error: Rank mismatch in argument ‘sx’ at (1) (rank-1 and scalar)
slatec.f90:190519:26:

190519 | call SCOPY (N, 0.E0, 0, WS(N3), 1)
| 1
Error: Rank mismatch in argument ‘sx’ at (1) (rank-1 and scalar)
slatec.f90:164331:17:

164331 | call SCOPY (N, 0.E0, 0, COEFF, 1)
| 1
Error: Rank mismatch in argument ‘sx’ at (1) (rank-1 and scalar)
slatec.f90:164376:20:

164376 | call SSORT (BKPT, DUMMY, NBKPT, 1)
| 1
Error: Rank mismatch in argument ‘y’ at (1) (rank-1 and scalar)
slatec.f90:164488:22:

164488 | call SCOPY (NORDP1, 0.E0, 0, G(IR,1), MDG)
| 1
Error: Rank mismatch in argument ‘sx’ at (1) (rank-1 and scalar)
slatec.f90:105293:58:

105293 | call DCKDER(M,N,X,FVEC,FJAC,LDFJAC,WA1,WA4,MODECH,ERR)
| 1
Error: Rank mismatch in argument ‘err’ at (1) (rank-1 and scalar)
slatec.f90:105304:30:

105304 | WA4(I),MODECH,ERR)
| 1
Error: Rank mismatch in argument ‘err’ at (1) (rank-1 and scalar)
slatec.f90:105375:58:

105375 | call DCKDER(M,N,X,FVEC,FJAC,LDFJAC,WA1,WA4,MODECH,ERR)
| 1
Error: Rank mismatch in argument ‘err’ at (1) (rank-1 and scalar)
slatec.f90:105389:58:

105389 | call DCKDER(1,N,X,FVEC(I),WA3,1,WA1,WA4(I),MODECH,ERR)
| 1
Error: Rank mismatch in argument ‘err’ at (1) (rank-1 and scalar)
slatec.f90:91652:20:

91652 | call DSORT (BKPT, DUMMY, NBKPT, 1)
| 1
Error: Rank mismatch in argument ‘dy’ at (1) (rank-1 and scalar)
slatec.f90:101869:52:

101869 | call DHFTI (W, MDW, MA, N, WS, MA, 1, TAU, KRANK, RNORM, WS(N2), &
| 1
Error: Rank mismatch in argument ‘rnorm’ at (1) (rank-1 and scalar)
slatec.f90:87987:20:

87987 | call DSORT (BKPT, DUMMY, NBKPT, 1)
| 1
Error: Rank mismatch in argument ‘dy’ at (1) (rank-1 and scalar)
slatec.f90:134655:62:

134655 | call DDERKF(DBVDER,NEQ,X,YHP,XXOP,INFO,RE,AE, &
| 1
Error: Rank mismatch in argument ‘rtol’ at (1) (rank-1 and scalar)
slatec.f90:134662:62:

134662 | call DDEABM(DBVDER,NEQ,X,YHP,XXOP,INFO,RE,AE, &
| 1
Error: Rank mismatch in argument ‘rtol’ at (1) (rank-1 and scalar)
slatec.f90:108283:35:

108283 | call DCSCAL(A,NRDA,N,M,SCALES,DUM,ROWS,RS,ANORM,SCALES,ISCALE, &
| 1
Error: Rank mismatch in argument ‘colsav’ at (1) (rank-1 and scalar)
slatec.f90:66413:19:

66413 | call DCOPY(NCOLS,ZERO,0,X,1)
| 1
Error: Rank mismatch in argument ‘dx’ at (1) (rank-1 and scalar)
slatec.f90:66482:19:

66482 | call DCOPY(NCOLS,ZERO,0,WW,1)
| 1
Error: Rank mismatch in argument ‘dx’ at (1) (rank-1 and scalar)
slatec.f90:66547:23:

66547 | call IVOUT(0,I,’(’’ FOUND NO VARIABLE TO ENTER’’)’,-4)
| 1
Error: Rank mismatch in argument ‘ix’ at (1) (rank-1 and scalar)
slatec.f90:66556:19:

66556 | call IVOUT(1,JBIG,’(’’ TRY TO BRING IN THIS COL.’’)’,-4)
| 1
Error: Rank mismatch in argument ‘ix’ at (1) (rank-1 and scalar)
slatec.f90:66577:23:

66577 | call IVOUT(0,I,’(’’ VARIABLE IS DEPENDENT, NOT USED.’’)’, &
| 1
Error: Rank mismatch in argument ‘ix’ at (1) (rank-1 and scalar)
slatec.f90:66617:23:

66617 | call IVOUT(0,I,’(’’ PIVOT IS ZERO, NOT USED.’’)’,-4)
| 1
Error: Rank mismatch in argument ‘ix’ at (1) (rank-1 and scalar)
slatec.f90:66641:19:

66641 | call IVOUT(0,I,’(’’ VARIABLE HAS BAD DIRECTION, NOT USED.’’)’, &
| 1
Error: Rank mismatch in argument ‘ix’ at (1) (rank-1 and scalar)
slatec.f90:66864:19:

66864 | call DCOPY(NCOLS,ZERO,0,X,1)
| 1
Error: Rank mismatch in argument ‘dx’ at (1) (rank-1 and scalar)
slatec.f90:18649:50:

18649 | call CPADD (NM+1,IERROR,AN,CN,B(J1),B(J1),B(J2))
| 1
Error: Type mismatch in argument ‘cbp’ at (1); passed REAL(4) to COMPLEX(4)
slatec.f90:225763:43:

225763 | 20 call DERKF(BVDER,NEQ,X,YHP,XXOP,INFO,RE,AE,IDID,WORK,KKKINT, &
| 1
Error: Rank mismatch in argument ‘rtol’ at (1) (rank-1 and scalar)
slatec.f90:225768:43:

225768 | 25 call DEABM(BVDER,NEQ,X,YHP,XXOP,INFO,RE,AE,IDID,WORK,KKKINT, &
| 1
Error: Rank mismatch in argument ‘rtol’ at (1) (rank-1 and scalar)
slatec.f90:194587:32:

194587 | call CSCALE(A,NRDA,N,M,SCALES,DUM,ROWS,RS,ANORM,SCALES,ISCALE,1)
| 1
Error: Rank mismatch in argument ‘colsav’ at (1) (rank-1 and scalar)
slatec.f90:38120:50:

38120 | call PPADD (NM+1,IERROR,AN,CN,B(J1),B(J1),B(J2))
| 1
Error: Type mismatch in argument ‘cbp’ at (1); passed REAL(4) to COMPLEX(4)
slatec.f90:6680:54:

6680 | call BSGQ8(F,T,BCOEF,N,K,ID,A,B,INBV,TOL,ANS,IFLG,WORK)
| 1
Error: Rank mismatch in argument ‘work’ at (1) (scalar and rank-1)
slatec.f90:17356:54:

17356 | W(IW3),W(IWD),W(IWW),W(IWU),PROC,CPROC)
| 1
Error: Type mismatch in argument ‘w1’ at (1); passed REAL(4) to COMPLEX(4)
slatec.f90:17359:56:

17359 | W(IW3),W(IWD),W(IWW),W(IWU),PROCP,CPROCP)
| 1
Error: Type mismatch in argument ‘w1’ at (1); passed REAL(4) to COMPLEX(4)
slatec.f90:20261:56:

20261 | LENWCM, IWORK, LENIW, F, F, NDE, MXSTEP, F, F, &
| 1
Error: Interface mismatch in dummy procedure ‘g’ at (1): ‘f’ is not a function
slatec.f90:23026:47:

23026 | call CFFTB1 (N,C,WSAVE,WSAVE(IW1),WSAVE(IW2))
| 1
Error: Type mismatch in argument ‘c’ at (1); passed COMPLEX(4) to REAL(4)
slatec.f90:23245:47:

23245 | call CFFTF1 (N,C,WSAVE,WSAVE(IW1),WSAVE(IW2))
| 1
Error: Type mismatch in argument ‘c’ at (1); passed COMPLEX(4) to REAL(4)
slatec.f90:23440:39:

23440 | call CFFTI1 (N,WSAVE(IW1),WSAVE(IW2))
| 1
Error: Type mismatch in argument ‘ifac’ at (1); passed REAL(4) to INTEGER(4)
slatec.f90:75106:32:

75106 | call DQRFAC(M,N,R,LDR,.FALSE.,IDUM,1,WA1,WA1,WA1)
| 1
Error: Rank mismatch in argument ‘ipvt’ at (1) (rank-1 and scalar)
slatec.f90:82992:56:

82992 | LENWCM, IWORK, LENIW, F, F, NDE, MXSTEP, F, F, &
| 1
Error: Interface mismatch in dummy procedure ‘g’ at (1): ‘f’ is not a function
slatec.f90:96462:33:

96462 | call DLLSIA(A,MDA,M,N,B,MDB,NB,RE,AE,KEY,MODE,NP, &
| 1
Error: Rank mismatch in argument ‘re’ at (1) (rank-1 and scalar)
slatec.f90:96467:37:

96467 | 10 call DULSIA(A,MDA,M,N,B,MDB,NB,RE,AE,KEY,MODE,NP, &
| 1
Error: Rank mismatch in argument ‘re’ at (1) (rank-1 and scalar)
slatec.f90:118232:37:

118232 | call DP1VLU (NDEG,NDER,X(I),R(I),YP,A)
| 1
Error: Rank mismatch in argument ‘yp’ at (1) (rank-1 and scalar)
slatec.f90:166330:43:

166330 | call EZFFT1 (N,WSAVE(2N+1),WSAVE(3N+1))
| 1
Error: Type mismatch in argument ‘ifac’ at (1); passed REAL(4) to INTEGER(4)
slatec.f90:179403:50:

179403 | call ICOPY (M2, ICOS(I2+1), 1, ICOS(I3+1), 1)
| 1
Error: Type mismatch in argument ‘ix’ at (1); passed REAL(4) to INTEGER(4)
slatec.f90:179408:50:

179408 | call ICOPY (M1, ICOS(I1+1), 1, ICOS(I3+1), 1)
| 1
Error: Type mismatch in argument ‘ix’ at (1); passed REAL(4) to INTEGER(4)
slatec.f90:179420:62:

179420 | call ICOPY (M2-J2+1, ICOS(I2+J2), 1, ICOS(I3+J3+1), 1)
| 1
Error: Type mismatch in argument ‘ix’ at (1); passed REAL(4) to INTEGER(4)
slatec.f90:179427:62:

179427 | call ICOPY (M1-J1+1, ICOS(I1+J1), 1, ICOS(I3+J3+1), 1)
| 1
Error: Type mismatch in argument ‘ix’ at (1); passed REAL(4) to INTEGER(4)
slatec.f90:203127:37:

203127 | call PVALUE (NDEG,NDER,X(I),R(I),YP,A)
| 1
Error: Rank mismatch in argument ‘yp’ at (1) (rank-1 and scalar)
slatec.f90:233888:31:

233888 | call QRFAC(M,N,R,LDR,.FALSE.,IDUM,1,WA1,WA1,WA1)
| 1
Error: Rank mismatch in argument ‘ipvt’ at (1) (rank-1 and scalar)
slatec.f90:238303:56:

238303 | LENWCM, IWORK, LENIW, F, F, NDE, MXSTEP, F, F, &
| 1
Error: Interface mismatch in dummy procedure ‘g’ at (1): ‘f’ is not a function
slatec.f90:244952:32:

244952 | call LLSIA(A,MDA,M,N,B,MDB,NB,RE,AE,KEY,MODE,NP, &
| 1
Error: Rank mismatch in argument ‘re’ at (1) (rank-1 and scalar)
slatec.f90:244957:36:

244957 | 10 call ULSIA(A,MDA,M,N,B,MDB,NB,RE,AE,KEY,MODE,NP, &
| 1
Error: Rank mismatch in argument ‘re’ at (1) (rank-1 and scalar)

1 Like

Is this really a “modernized” version of SLATEC? It doesn’t appear as such, meaning the TYPE, RANK, and INTERFACE mismatches have never been permitted by the standard - as explicitly as shown any way.

And Fortran compilers at least since the days of Fortran 95 i.e., circa 1997 and thereafter have generally issued diagnostics toward this.

g95 must have been rather permissive to let such issues pass.

Perhaps SLATEC functionality (along with modernized refactoring of existing code if licensing would allow) can be “rolled” into the current “standard library” effort and coded in a standard-conforming manner?

Regarding g95 being permissive, compiling with g95 -std=f95 the only errors are with “H formats”:

1004 FORMAT(1X,3HROW,I4,2X,1P,8D14.5)
1
Error: The H format specifier is a deleted language feature in format string at (1)
In file slatec.f90:103394

Compiling with g95 -c -Wall slatec.f90 works produces many warnings such as

In file slatec.f90:224898

subroutine RFFTI1 (N, WA, IFAC)
2
Warning (155): Inconsistent types (REAL(4)/INTEGER(4)) in actual argument lists at (1) and (2)

The file slatec.f90 has almost 300K lines of code. Maybe some tools such as plusFORT are needed for modernizing lage FORTRAN code bases.

Compiling with gfortran -c -w -std=legacy -fallow-invalid-boz the only error is

slatec.f90:221350:0:

150867 | COMMON /DDEBD1/ ROWND,CONIT,CRATE,EL(13),ELCO(13,12),HOLD,RC,RMAX, &
| 2

221350 | FUNCTION RC (X, Y, IER)
|
Error: Global entity ‘rc’ at (1) cannot appear in a COMMON block at (2)
slatec.f90:221350:0: Error: (1)
slatec.f90:277754:17: Error: Global entity ‘rc’ at (1) cannot appear in a COMMON block at (2)

Hello @Beliavsky,

As you have encountered, digging straight into SLATEC is not necessarily the best way to start. I think we need to follow @FortranFan’s advice:

A few individuals have started such refactoring efforts previously (e.g. PCHIP) for some of the subpackages.

There is also a good blog post on the topic: Degenerate Conic | SLATEC

It also compiled straightforwardly with my gfortran [gcc version 8.3.0 (Debian 8.3.0-6)] but producing a .o of 5MB.

I agree that it is not the modernized way of developing a library we’re looking for, but I guess it’s good to see previous attempts to organize the messy wold of Fortran (Open Source) libraries. Also to remind us the importance of this project and find a way out to standardize a mathematical library.

I guess a good starting point is to discuss what this mathematical library should contain and which is the correct approach to define the calls to the routines. This can easily be taken from other libraries out there. Some of you commented that Julia and C++ (if I remember correctly) has this properly done. One can also follow the GSL documentation https://www.gnu.org/software/gsl/doc/html/index.html which I find clear, neat and complete. The thing that I don’t like about the GSL is the calls to the routines and I hope this can be better done in the stdlib.

It also compiled straightforwardly with my gfortran [gcc version 8.3.0 (Debian 8.3.0-6)] but producing a .o of 5MB.

I agree that it is not the modernized way of developing a library we’re looking for, but I guess it’s good to see previous attempts to organize the messy wold of Fortran (Open Source) libraries. Also to remind us the importance of this project and find a way out to standardize a mathematical library.

LAPACK is still written in FORTRAN 77 I believe, but Matlab, R, and Python/SciPy have nice interfaces to call it, and there is also LAPACK95, a Fortran95 interface to LAPACK. Modern Fortran interfaces could also be created for SLATEC, and I think that would take less time than recreating the functionality from scratch. OTOH, other goals of a library may include
(1) Enabling the user to understand algorithms, possibly with a view to extending them
(2) Algorithms beyond what’s in the classic FORTRAN 77 libraries.
(3) Showcasing the features of Modern Fortran

1 Like

I pretty much agree with that. I think the first realistic step to have something working in the near future is to standardize a way to interface any code, with these interfaces showing the three points you mention.

Then maybe in the farther future, I hope developers decide to develop their routines following the convention stated in the stdlib. Making them reusable and easy-to-use code.

1 Like