I have suggested in a few GitHub issues that the Fortitude linter detect the use of non-standard intrinsic procedures and suggest standard replacements. Can we create a list of non-standard intrinsics by compiler and their standard alternatives?` Ideally we would have short programs showing the how the usage of non-standard intrinsics can be replaced by standard ones. Sometimes the non-standard intrinsic will not have an exact equivalent.
gfortran
system, execute_command_line
float, real
dfloat, dble or preferably replace dfloat(x) with real(x, kind=dp) with dp a double precision kind parameter
iargc, command_argument_count
getarg, get_command_argument
etime, system_clock (gfortran documentation saysetime can be invoked as either a subroutine or function)
Shouldn’t the explicit use of items coming from a non-standard intrinsic module be excluded?
I mean, Intel’s systemqq requires use ifport, whereas nargs, and getarg do not.
I think the former should be listed along with the name of the non-standard intrinsic module, since a linter should still suggest a standard replacement.
I had frustrations with converting between Date and Time intrinsic procedures between compilers when my Company went to different Fortran software. Some older versions used *4 integers and may have limited the year portion to 2 digits upon output. I encountered compilers with character-based Date and Time which I think you had to parse in two-digit chunks “cut” out of a contiguous character variable. One of the packages had some kind of packed 2-integer internal variable (in my limited understanding and memory). At any rate, since many of our old programs were written with multiple calls to date and time because each programmer re-invented page heading routines, confusion abounded. I’m sure many of you recall the “great Millennial fiasco of 2000” of converting 2-digit years to 4-digit and hoping that no data bases extended back before 1900.
Some of the “players” in our software evolution were: ProFortran, Microsoft Fortran and Digital Visual Fortran. I fell in love with Digital’s packaging and bright colored illustrations on their manual covers. I even back-filled my under-size three-ring MS Fortran binders with Digital Visual reference manual pages.
Seems in earlier years we had to write our own custom functions to perform “floor”, “ceiling” and “mod” functionality. I was told that statistics majors hated random-number routines because they were never purely random, mathematically.
The intrinsics built into fpt are listed below. Many of the non-standard ones come from VMS and were inherited by DVF/CVF, HP-UX, and ifort/ifx. Others come from Gould-SEL MPX, Lahey and Salford. Writing demonstration programs for all these would be significant work, but could be done. fpt already evaluates most of those which are not environment-specific, and we have test programs which cover many of them. How useful would this be?
A note: fpt uses a trie search for names which gives a sequential integer index for each name. Comments in the list below show where the sequential numbers index switch lists in the code, and the $ character marks place-holders where the names are already the names of keywords - e.g. REAL.
! Intrinsics (Taken from VAX FORTRAN)
! **** WARNING **** These names index a switch list in INTRIN ****
SQRT DSQRT QSQRT CSQRT CDSQRT
LOG ALOG DLOG QLOG CLOG CDLOG
LOG10 ALOG10 DLOG10 QLOG10
EXP DEXP QEXP CEXP CDEXP
SIN DSIN QSIN CSIN CDSIN
SIND DSIND QSIND
COS DCOS QCOS CCOS CDCOS
COSD DCOSD QCOSD
TAN DTAN QTAN
TAND DTAND QTAND
ASIN DASIN QASIN
ASIND DASIND QASIND
ACOS DACOS QACOS
ACOSD DACOSD QACOSD
ATAN DATAN QATAN
ATAND DATAND QATAND
ATAN2 DATAN2 QATAN2
ATAN2D DATAN2D QATAN2D
SINH DSINH QSINH
COSH DCOSH QCOSH
TANH DTANH QTANH
ABS IIABS JIABS DABS QABS CABS CDABS
IABS
INT IINT JINT IIDINT JIDINT IIQINT JIQINT
IDINT
IQINT
AINT DINT QINT
NINT ININT JNINT IIDNNT JIDNNT IIQNNT JIQNNT
IDNINT
IQNINT
ANINT DNINT QNINT
ZEXT IZEXT JZEXT
REAL$ ! Note $ - this is a place holder
FLOATI FLOATJ SNGL SNGLQ
DBLE DBLEQ
QEXT QEXTD
IFIX IIFIX JIFIX
FLOAT
DFLOAT DFLOTI DFLOTJ
QFLOAT
CMPLX
DCMPLX
DREAL
AIMAG DIMAG IMAG ! IMAG is non-standard
CONJG DCONJG
DPROD
MAX IMAX0 JMAX0 AMAX1 DMAX1 QMAX1
MAX0
MAX1 IMAX1 JMAX1
AMAX0 AIMAX0 AJMAX0
MIN IMIN0 JMIN0 AMIN1 DMIN1 QMIN1
MIN0
MIN1 IMIN1 JMIN1
AMIN0 AIMIN0 AJMIN0
DIM IIDIM JIDIM DDIM QDIM
IDIM
MOD IMOD JMOD AMOD DMOD QMOD
SIGN IISIGN JISIGN DSIGN QSIGN
ISIGN
IAND IIAND JIAND
IOR IIOR JIOR
IEOR IIEOR JIEOR
NOT INOT JNOT
ISHFT IISHFT JISHFT
IBITS IIBITS JIBITS
IBSET IIBSET JIBSET
BTEST BITEST BJTEST
IBCLR IIBCLR JIBCLR
ISHFTC IISHFTC JISHFTC
LEN
INDEX
CHAR
ICHAR
LLT LLE LGT LGE
SIZEOF
LOC
! Gould-SEL ADDR equivalent to LOC
ADDR
! VAX special intrinsic functions
%LOC %VAL %REF %DESCR
! Lahey special intrinsics
INT2
INT4
I2NINT
I2ABS
I2MOD
I2SIGN
I2DIM
I2MAX0
I2MIN0 ! Must be last intrinsic original set
! Intrinsic functions from DEC Language Reference Manual 1997
! Note that many are already in the list above
! F90
IABS
ABS
DABS
CABS
ACHAR
ACOS
DACOS
ADJUSTL
ADJUSTR
AIMAG
AINT
DINT
ALL
ALLOCATED
ANINT
DNINT
ANY
ASIN
DASIN
ASSOCIATED
ATAN
DATAN
ATAN2
DATAN2
BIT_SIZE
BTEST
CEILING
CHAR
CMPLX
CONJG
COS
DCOS
CCOS
COSH
DCOSH
COUNT
CSHIFT
DBLE
DIGITS
IDIM
DIM
DDIM
DOT_PRODUCT
DPROD
EOSHIFT
EPSILON
EXP
EXPONENT
FLOOR
FRACTION
HUGE
IACHAR
IAND
IBCLR
IBITS
IBSET
ICHAR
IEOR
INDEX
INT
IFIX
IDINT
IOR
ISHFT
ISHFTC
KIND
LBOUND
LEN
LEN_TRIM
LGE
LGT
LLE
LLT
LOG
ALOG
DLOG
CLOG
LOG10
ALOG10
DLOG10
LOGICAL$
MATMUL
MAX
MAX0
AMAX0
MAX1
AMAX1
DMAX1
MAXEXPONENT
MAXLOC
MAXVAL
MERGE
MIN
MIN0
AMIN0
MIN1
AMIN1
DMIN1
MINEXPONENT
MINLOC
MINVAL
MOD
AMOD
DMOD
MODULO
!!! MVBITS This is a subroutine
NEAREST
NINT
IDNINT
NOT
PACK
PRECISION
PRESENT
PRODUCT
RADIX
RANGE
REAL$
FLOAT
SNGL
REPEAT
RESHAPE
RRSPACING
SCALE
SCAN
SELECTED_INT_KIND
SELECTED_REAL_KIND
SET_EXPONENT
SHAPE
SIGN
ISIGN
DSIGN
SIN
DSIN
CSIN
SINH
DSINH
SIZE
SPACING
SPREAD
SQRT
DSQRT
CSQRT
SUM
TAN
DTAN
TANH
DTANH
TINY
TRANSFER
TRANSPOSE
TRIM
UBOUND
UNPACK
VERIFY
! Non-standard (blue) and post Fortran 90
IIABS
KIABS
QABS
CDABS
JIABS
ZABS
QACOS
ACOSD
DACOSD
QACOSD
DIMAG
QINT
QNINT
ASIND
DASIND
QASIND
ATAND
DATAND
QATAND
QATAN2
ATAN2D
DATAN2D
QATAN2D
BITEST
BKTEST
DCONJG
QCOS
CDCOS
ZCOS
COSD
DCOSD
QCOSD
QCOSH
COTAN
DCOTAN
DBLEQ
DCMPLX
DFLOAT
DFLOTI
DFLOTJ
DFLOTK
IIDIM
KIDIM
QDIM
QEXP
CDEXP
ZEXP
FP_CLASS
IARGCOUNT
IARGPTR
IBCHNG
IIBCLR
JIBCLR
KIBCLR
IIBITS
JIBITS
KIBITS
IIBSET
JIBSET
KIBSET
IIEOR
JIEOR
KIEOR
ILEN
IIFIX
IINT
JFIX
KIFIX
KINT
IIDINT
HFIX
JINT
KIDINT
IIQINT
IQINT
KIQINT
INT1
INT2
INT4
INT8
IIOR
JIOR
KIOR
ISHA
ISHC
IISHFT
JISHFT
KISHFT
IISHFTC
JISHFTC
KISHFTC
ISHL
ISNAN
LOC
QLOG
CDLOG
QLOG10
MALLOC
IMAX0
AIMAX0
KMAX0
AKMAX0
IMAX1
KMAX1
QMAX1
JMAX0
AJMAX0
IMIN0
AIMIN0
KMIN0
AKMIN0
IMIN1
KMIN1
QMIN1
JMIN0
AJMIN0
IMOD
KMOD
QMOD
JMOD
ININT
KNINT
IIDNNT
KIDNNT
IIQNNT
IQNINT
KIQNNT
JNINT
JIDNNT
JIQNNT
NULL
NUMBER_OF_PROCESSORS
NWORKERS
PROCESSORS_SHAPE
QEXT
QEXTD
QFLOAT
RAN
FLOATI
FLOATK
SNGLQ
FLOATJ
SECNDS
IISIGN
KISIGN
QSIGN
JISIGN
QSIN
CDSIN
ZSIN
SIND
DSIND
QSIND
SIZEOF
QSQRT
CDSQRT
QTAN
TAND
DTAND
QTAND
QTANH
POW ! C Intrinsic used in APPRASE
IARGC
ZEXT
IZEXT
JZEXT
COMMAND_ARGUMENT_COUNT
ERF ! Fortran 2008
DERF ! R*8 only ERF
GAMMA ! Fortran 2008
DGAMMA ! Gnu extension
EOF ! CVF, ifort but not standard
DEFINED ! DEC$ IF intrinsic
SYSTEM$FUN ! Placeholder
AND$ ! Placeholder
OR$ ! Placeholder
XOR$ ! Placeholder
KZEXT ! Must be last
! End of intrinsic functions - Intrinsic subroutines
DATE_AND_TIME
MVBITS
RANDOM_NUMBER
RANDOM_SEED
CPU_TIME
EXECUTE_COMMAND_LINE
GET_ENVIRONMENT_VARIABLE
GET_COMMAND
GET_COMMAND_ARGUMENT
!
! Non-standard
FLUSH$
EXIT$
SYSTEM$
DATE
TIME
! Standard and Last in group
SYSTEM_CLOCK
! End of intrinsic subroutines - SYSTEM_CLOCK must remain last
@Beliavsky reminded us that gfortran has a non-standard intrinsic subroutine system. So do all four of ifort, ifx, g95 and AMD flang. All except g95 also have the standard alternative execute_command_line, which was not yet implemented when g95 development ceased.
Unlike the function systemqq, the subroutine system does not need a non-standard module.
Most of the compilers can warn or reject intrinsics not specified in the standard, I believe. For gfortran -std=2018 -Wintrinsics-std for example. NVfortran warns by default if you use a variable name the same as intrinsic, and so on. -pedantic can be useful too. Other compilers have related switches.
Note some have a subroutine called SYSTEM, some have a function; some allow both. There was at least one system that hung if the SYSTEM function was called in a WRITE statement in the past.
There are also options for some loaders where you can say not to load the intrinsic libraries and then see what routines are not satisfied which was something we used to use to clean out such usage in the past.
At one time only Cray was supporting the PFX routines, but most of the functionality was there as an extension or was easy to add. For example, everyone had a file status procedure, or it was not too hard to add trig functions that took degrees by calling the radians ones in little procedures and so on. So a central group made a PFX look-alike using compiler extensions if needed, then Fortran-based DIY routines if possible (usually true for math-related ops but not system ops), then procedures that called C or called system commands. It isolated everyone just like POSIX was implemented everywhere. Maybe some fortran-stdlib routines could use preprocessor directives to do the same. The main advantage of looking for compiler-supplied functions is the vendor often took care of the OS/system dependencies so you did not have to support a DEC and Cray and HP-UX and SunOS and Prime and … system interface using machine code or Pascal or (later) C.
So for example, a lot of compilers have some variant of ISTTY so just a little wrapper makes it relatively “standard”.
module clean
external system
internal cos
end module clean
program testit
use clean
use clean, only : cosine=> cos ! this would let you rename an intrinsic!
real :: cos ! will not allow it
call system('date') ! will not allow it
write(*,*)cosine(0.0)
end program testit
If the compiler presents a non-standard procedure as “intrinsic” a module filled with a lot of names you do not want to use prevent it from being called, and listing all the “good” names as intrinsic prevents the name from being used as a variable, … not perfect as you might not know all the names but handly.
And some compilers and loaders still give you names and where they are loaded from. Using something that looks at that, plus the output from ldd(1) should be part of everyone’s code release process, so you know what you are requiring in my opinion.
When a linter encounters isatty or ttynam, are there standard intrinsics it could suggest using intead? Instead of isatty test if the unit equals input_unit from iso_fortran_env?
Not that I am aware of; a LUN could be INPUT_UNIT and not be attached to a tty though, so that would only work if INPUT_UNIT was preassigned and had not been closed and was not redirected or coming from a pipe; and the output of an INQUIRE is not standardized enough to use it portably. On a specific platform with a specific compiler you can sometimes use INQUIRE to see if the name contains /dev/tty* or something like that, but it is not portable.
program testit
#ifdef __INTEL_COMPILER
use IFPORT ! needed by Intel ifort/ifx
#endif
#ifdef __NVCOMPILER
use DFPORT ! needed by NVfortran
#endif
use, intrinsic :: iso_fortran_env, only: stdin=>input_unit
implicit none
character(len=4096) :: filename
logical :: l1,l2,l3,l4,l5
write(*,*)'ISATTY(stdin)=',isatty(stdin)
write(*,*)'STDIN=',stdin
inquire(unit=stdin,opened=l1,named=l2,name=filename)
if(l1)then
write(*,*)'FILENAME=',trim(filename)
endif
end program testit
run this with different compilers and different systems and you will see how much is left up to the compiler in the standard. The file may not be named, may be something like /dev/stdin or just stdin or a unique filename just running the program.
Then try it with “echo A|./testit” and “./testit <filename” and so on.
@urbanjost mentioned the POSIX “PXF” API that only a few vendors bothered to implement. Cray->SGI, and later, Intel in particular. With it, you can use the PXFISATTY and PXFTTYNAME subroutines. Both require a file descriptor, not a Fortran unit number, as an input argument. If you want to obtain the file descriptor for a certain Fortran unit number, just call PXFFILENO.
Unfortunately, PXFFILENO is one of the few PXF routines that can’t be written somewhat portably. It needs to know the internals of the particular Fortran compilers’ I/O library.
Maybe on this thread I should repeat my complaint that there is no Fortran Standard sort procedure. Lots of vendors have sort procedures in their libraries. But they are all different. I’ve mentioned this to several members of the Fortran committee over the years, and there are a couple of issues on this at j3-fortran/fortran_proposals. (One of which I wrote.) But no action.
Calling the C qsort function via C Interop is certainly possible. But it has drawbacks as well.
SORT, and certainly UPPER and LOWER, at least for ASCII at a minimum. I mistakenly thought those made it in with SPLIT. The other avenue is the fpm repository and the stdlib project. I thought there would be a path from private open-source projects to fpm projects to the fpm repository to the stdlib project developing that would provide for initial concepts to be proposed, compete, become reliably available, go into stdlib and ultimately have vendor-supplied versions supplied, gradually reducing the number of compiler-specific extensions.
That has been moving slower than I expected. I thought a new version of a repository was on the verge of going online and then have not heard.
It would be a natural place to put a “reserved” module as discussed in this post that could reserve standard names and intrinsics and prevent the use of common extensions and let people play with the pros and cons of doing so, for one.
Thinking of something just about every compiler has is something to return the day of the week and the month. I am playing with variations on what an underlying structure should look like for retaining dates. I personally started with the same array as returned by DATE_AND_TIME but have reason to try using a Base and Seconds model, or a 64-bit array like date and time but with higher-precision seconds or adding an optional 9th value that indicates how precise the seconds are; whether locale is important; particularly Unicode support for labels; whether everyone should pretend leap-seconds never existed; how best to handle time zones and daylight savings or whether to just wrap the C date and time functions. It used to drive me crazy there was no standard date routine at all, but DATE_AND_TIME did not quite resolve all the issues. My own
fpm-compatible version is at GitHub - urbanjost/M_time: module of procedures that expand on the Fortran DATE_AND_TIME(3f) intrinsic.
Discussions started on fortran-stdlib about providing at least a Civil Calendar interface for the Gregorian calendar and the thought would be that a consensus would develop from the various packages available following the development path described above. Seems to have gotten as far as having a standard SORT.
Can someone connected with the Standards Committee enlighten us as to why these have never made it into the standard. It just seems like a no-brainer that these should be standard Fortran intrinsics. These three would probably get more use in a day than TAND, SIND etc would get in a week.
My theory is that their absence is there to make sure no one starts using Fortran that doesn’t want to re-invent every wheel ever rolled . Does anyone not have a version of LOWER()?
I agree that the string utilities would get more use than sind. The best answer I can come up with is that upper can be implemented in an external library (like stdlib above), while sind might require a very specific internal compiler implementation and optimizations. @sblionel might remember more, I think the string utilities have been proposed before.