Degenerate Conic

Algorithms • Modern Fortran Programming • Orbital Mechanics

Oct 24, 2021

Fortran Filesystem Blues

files

One of my major pet peeves about Fortran is that it contains virtually no high-level access to the file system. The file system is one of those things that the Fortran standard pretends doesn't exist. It's one of those idiosyncratic things about the Fortran standard, like how it uses the word "processor" instead of "compiler", and doesn't acknowledge the existence of source code files so it doesn't bother to recommend a file extension for Fortran (gotta preserve that backward compatibility just in case punch cards come back).

There are various hacky workarounds to do various things that poor Fortran programmers have had to use for decades. Basically, all you have is OPEN, CLOSE, READ, WRITE, and INQUIRE. Here are a few examples:

Deleting a file

Here's a standard Fortran routine that can be used to delete a file:

function delete_file(name) result(istat)

  implicit none

  character(len=*),intent(in) :: name
  integer :: istat

  integer :: iunit

  open(newunit=iunit,status='OLD',iostat=istat)
  if (istat==0) close(iunit,status='DELETE',iostat=istat)

end function delete_file

As you can see, it's just a little trick, using a feature of CLOSE to delete a file after closing it (but first, we had to open it). Of course, note that the error codes are non-standard (the Fortran standard also doesn't consider this information important and lets the different compilers do whatever they want -- so of course, they all do something different). And of course, there is no exception handling in Fortran either (a post for another time).

Creating a directory

There is absolutely no standard ability in Fortran to create or delete a directory. Again, Fortran basically pretends that directories don't exist. Note that the Intel Fortran Compiler provides a super useful non-standard extension of the INQUIRE statement to allow it to be used to get information about directories. It's a pretty ridiculous state of affairs (Fortran added a bazillion IEEE routines in Fortran 2018 for some reason that nobody needed, but it still doesn't have something like this that everybody has needed for decades). Intel's IFPORT portability module provides many useful (non-standard) routines for accessing the file system (for example DELFILESQQ for deleting files and DELDIRQQ for deleting a directory). I use these all the time and the fact that they are non-standard and not present in other compilers is a major source of annoyance.

For some file or directory operations, you can always resort to using system calls, and thus have to provide different methods for different platforms (of course Fortran provides no standard way to get any information about the platform, so you have to resort to non-standard, possibly compiler-specific, preprocessor directives to do that). For example, to create a directory you could use:

subroutine make_directory(name)

  implicit none

  character(len=*),intent(in) :: name

  call execute_command_line ('mkdir '//name)

end subroutine make_directory

That one was easy because "mkdir" works on macOS, Window, and Linux. See previous post about getting command line calls into strings, which can also be useful for some things like this.

Getting a list of files

How about getting a list of all the files that match a specific pattern? Again, this can be done if you are using the Intel compiler using the IFPORT module GETFILEINFOQQ routine:

function get_filenames(pattern, maxlen) result(list)

  use ifport

  implicit none

  character(len=*),intent(in) :: pattern
  integer,intent(in) :: maxlen
  character(len=maxlen),dimension(:),allocatable :: list

  integer(kind=int_ptr_kind()) :: handle
  type(file$infoi8) :: info
  integer :: length

  allocate(list(0))
  handle = file$first
  do
    length = GETFILEINFOQQ(trim(pattern), info, handle)
    if ((handle==file$last) .or. (handle==file$error)) exit
    list = [list, info%name]
  end do

end function get_filenames

The file$infoi8 type is some super-weird non-standard Intel thing. Note that this example only returns the file names, not the full paths. To get the full path is left as an exercise to the reader. Also note that Fortran doesn't provide a good string class, so we just set a maximum string length as an argument to this function (but note that Intel is only returning a 255-character string anyway).

Final thoughts

There are various libraries out there that can do some of this. For example, M_system (a Fortran module interface for calling POSIX C system routines). Hopefully, a comprehensive set of filsystem routines will eventually make it into the Fortran Standard Library.

See also

Dec 18, 2020

oneAPI

intel-logo-vector

Intel recently released its new oneAPI Toolkit, which had been in beta for a while. According to their documentation, oneAPI includes various products:

The big news here is that this is all now entirely free to use. They are all available for Windows, Linux, and macOS. The Fortran compiler also now includes all of the Fortran 2018 standard. Apparently, Intel will still sell you a license, but it seems the only reason to buy one would be to get the Premier Support.

See also

Dec 18, 2019

Intel Fortran Compiler 19.1

intel-logo-vector

Intel has released version 19.1 the Intel Fortran Compiler (part of Intel Parallel Studio XE 2020). According to the release notes, the new version adds a lot of features from Fortran 2018:

  • Enhancements to the IMPLICIT statement allow specifying that all external procedures must declared EXTERNAL
  • Enhancements to the GENERIC statement permit it to be used to declare generic interfaces
  • The locality of variables may now be specified on a DO CONCURRENT statement
  • Enhancements to edit descriptor forms E, D, EN, ES, and G allow a field width of zero, analogous to the F edit descriptor
  • The exponent width e in a data edit descriptor may now be zero, analogous to a field width of zero
  • The RN edit descriptor now rounds to nearest as specified by Fortran 2018 and ISO/IEC/IEEE 60559:2011
  • The EX edit descriptor allows for hexadecimal format output of floating point values. Hexadecimal format floating point values are allowed on input.
  • SIZE= may be specified for non-advancing I/O
  • The values for SIZE= and POS= in an INQUIRE statement for pending asynchronous operations have been standardized
  • The value assigned to the RECL= specifier in an INQUIRE statement now has standardized values
  • A new form of the intrinsic function CMPLX does not require the KIND= keyword if the first argument is type COMPLEX
  • The arguments to the SIGN function may be of different kinds
  • INTEGER and LOGICAL arguments to intrinsic procedures are no longer required to be of default kind
  • The named constants STAT_FAILED_IMAGE and STAT_UNLOCKED_FAILED_IMAGE have been defined in the intrinsic ISO_FORTRAN_ENV module
  • The non-block DO statement and the arithmetic IF statement are now deleted in Fortran 2018.
  • COMMON, EQUIVALENCE and BLOCKDATA statements are now obsolescent
  • The labeled form of DO loops is now obsolescent
  • Locality of variables in DO CONCURRENT constructs can now be declared on the DO CONCURRENT statement
  • Specific names of intrinsic procedures are now obsolescent
  • FAIL IMAGE statement allows debugging recovery code for failed images without having to wait for an actual image failure
  • The named constants STAT_FAILED_IMAGE and STAT_UNLOCKED_FAILED_IMAGE have been defined in the intrinsic ISO_FORTRAN_ENV module
  • An optional argument STAT= has been added to ATOMIC_REF and ATOMIC_DEFINE intrinsic procedures
  • Optional STAT= and ERRMSG= specifiers have been added to the MOVE_ALLOC intrinsic procedure, to image selectors, and to the CRITICAL statement and construct
  • Atomic subroutines ATOMIC_ADD, ATOMIC_AND, ATOMIC_CAS, ATOMIC_FETCH_ADD, ATOMIC_FETCH_AND, ATOMIC_FETCH_OR, ATOMIC_FETCH_XOR, ATOMIC_OR, and ATOMIC_XOR have been implemented
  • Collective subroutines CO_BROADCAST, CO_MAX, CO_MIN, CO_REDUCE, and CO_SUM have been implemented
  • The SELECT RANK construct has been implemented allowing manipulation of assumed rank dummy arguments
  • The compiler will now diagnose the use of nonstandard intrinsic procedures and modules as required by Fortran 2018
  • Transformational intrinsic functions from the intrinsic modules ISO_C_BINDING, IEEE_ARITHMETIC, and IEEE_EXCEPTIONS are now allowed in specification expressions
  • You can now specify the optional argument RADIX for the IEEE_GET_ROUNDING_MODE and IEEE_SET_ROUNDING_MODE intrinsic module procedures
  • The optional ROUND argument has been added to the IEEE_RINT function in the intrinsic module IEEE_ARITHMETIC
  • The intrinsic module IEEE_ARITHMETIC now includes the functions IEEE_FMA, IEEE_SIGN_BIT, IEEE_NEXT_UP and IEEE_NEXT_DOWN
  • The intrinsic module procedures IEEE_MAX, IEEE_MIN, IEEE_MAX_MAG, and IEEE_MIN_MAG have been implemented
  • The intrinsic module procedures IEEE_INT and IEEE_REAL have been implemented
  • The intrinsic module IEEE_EXCEPTIONS now contains a new derived type, IEEE_MODES_TYPE, which can be used to save and restore the IEEE_MODES using the IEEE_GET_MODES and the IEEE_SET_MODES intrinsic module procedures
  • A new rounding mode, IEEE_AWAY has been added
  • SUBNORMAL is now synonymous with DENORMAL
  • IEEE_QUIET_EQ, IEEE_QUIET_NE, IEEE_QUIET_LT, IEEE_QUIET_LE, IEEE_QUIET_GT, IEEE_QUIET_GE, IEEE_SIGNALING_EQ, IEEE_SIGNALING_NE, IEEE_SIGNALING_GT, IEEE_SIGNALING_GE, IEEE_SIGNALING_LT, and IEEE_SIGNALING_LE intrinsic module procedures have been implemented

The Intel Fortran Compiler has full support for the Fortran 2008 standard and includes most features from the Fortran 2018 standard.

See also

Sep 13, 2018

Intel Fortran Compiler 19.0

intel-logo-vector

Intel has just released v19 of the Intel Fortran Compiler (part of Intel Parallel Studio XE 2019). The new release adds some new features from the upcoming Fortran 2018 standard:

  • Coarray events
  • Intrinsic function coshape
  • Default accessibility for entities accessed from a module
  • Import Enhancements
  • All standard procedures in ISO_C_BINDING other than C_F_POINTER are now PURE

Presumably, it also include some bug fixes. Intel used to provide a list of bug fixes, but they seem to have stopping doing that for some reason.

See also

Sep 12, 2017

Intel Fortran Compiler 18.0

intel-logo-vector

Intel has just released version 18 of the Intel Fortran Compiler (part of Intel Parallel Studio XE 2018). At long last, this release includes full support for the Fortran 2008 standard. The updates since the previous compiler release include:

  • COMPILER_OPTIONS and COMPILER_VERSION in ISO_FORTRAN_ENV
  • Complex arguments to trigonometric and hyperbolic intrinsic functions
  • FINDLOC intrinsic function
  • Optional argument BACK in MAXLOC and MINLOC intrinsic functions
  • Multiple type-bound procedures in a PROCEDURE list
  • Passing a non-pointer data item to a pointer dummy argument
  • Polymorphic assignment with allocatable Left Hand Side (LHS)
  • Allocatable components of recursive type and forward reference
  • Data statement restrictions removed

In addition, the new release also includes support for all the features from "Technical Specification 29113 Further Interoperability with C", planned for inclusion in Fortran 2015. These include:

  • Assumed type (TYPE(*))
  • Assumed rank (DIMENSION(..))
  • Relaxed restrictions on interoperable dummy arguments
  • ISO_Fortran_binding.h C include file for use by C code manipulating "C descriptors" used by Fortran

Hopefully, it won't take so long to get the compiler up to full Fortran 2015 compliance (see a previous post for a list of new Fortran 2015 features).

See also

Sep 10, 2016

Intel Fortran Compiler 17.0

intel-logo-vector-01

Intel has announced the availability of version 17.0 of the Intel Fortran Compiler (part of Intel Parallel Studio XE 2017). Slowly but surely, the compiler is approaching full support for the current Fortran 2008 standard. New Fortran 2008 features added in this release are:

  • TYPE(intrinsic-type)
  • Pointer initialization
  • Implied-shape PARAMETER arrays
  • Extend EXIT statement to all valid construct names
  • Support BIND(C) in internal procedures

In addition, the compiler now also supports the standard auto-reallocation on assignment by default (previously, you had to use a special compiler flag to enable this behavior).

See also

Feb 28, 2016

Multidimensional Linear Interpolation

Some years ago, I needed a Fortran routine to do linear interpolation of a multidimensional (up to 6D) data set. Not wanting to reinvent the wheel, I ended up using a routine called FINT from CERNLIB (documentation here). It is written in Fortran 66, and has some hard-coded limits on the number of dimensions that can be used, but these are not fundamental to the algorithm. With a few minor changes, the routine can be used for interpolation of any number of dimensions. I present below a modern Fortran version that removes the limitations. Note that the original code is GPL licensed, thus so is this modification.

function fint(narg,arg,nent,ent,table)

use iso_fortran_env, only: wp => real64

implicit none

real(wp) :: fint  
integer,intent(in) :: narg  
integer,dimension(narg),intent(in) :: nent  
real(wp),dimension(narg),intent(in) :: arg  
real(wp),dimension(:),intent(in) :: ent  
real(wp),dimension(:),intent(in) :: table

integer,dimension(2**narg) :: index  
real(wp),dimension(2**narg) :: weight  
logical :: mflag,rflag  
real(wp) :: eta,h,x  
integer :: i,ishift,istep,k,knots,lgfile,&  
           lmax,lmin,loca,locb,locc,ndim

!some error checks:  
if (size(ent)/=sum(nent)) &  
    error stop 'size of ent is incorrect.'  
if (size(table)/=product(nent)) &  
    error stop 'size of table is incorrect.'  
if (narg<1) &  
    error stop 'invalid value of narg.'

lmax = 0  
istep = 1  
knots = 1  
index(1) = 1  
weight(1) = 1.0_wp

main: do i = 1 , narg  
    x = arg(i)  
    ndim = nent(i)  
    loca = lmax  
    lmin = lmax + 1  
    lmax = lmax + ndim  
    if ( ndim>2 ) then  
        locb = lmax + 1  
        do  
            locc = (loca+locb)/2  
            if ( x<ent(locc) ) then  
                locb = locc  
            else if ( x==ent(locc) ) then  
                ishift = (locc-lmin)*istep  
                do k = 1 , knots  
                    index(k) = index(k) + ishift  
                end do  
                istep = istep*ndim  
                cycle main  
                else  
                loca = locc  
            end if  
            if ( locb-loca<=1 ) exit  
        end do  
        loca = min(max(loca,lmin),lmax-1)  
        ishift = (loca-lmin)*istep  
        eta = (x-ent(loca))/(ent(loca+1)-ent(loca))  
    else  
        if ( ndim==1 ) cycle main  
        h = x - ent(lmin)  
        if ( h==0.0_wp ) then  
            istep = istep*ndim  
            cycle main  
        end if  
        ishift = istep  
        if ( x-ent(lmin+1)==0.0_wp ) then  
            do k = 1 , knots  
                index(k) = index(k) + ishift  
            end do  
            istep = istep*ndim  
            cycle main  
        end if  
        ishift = 0  
        eta = h/(ent(lmin+1)-ent(lmin))  
    end if  
    do k = 1 , knots  
        index(k) = index(k) + ishift  
        index(k+knots) = index(k) + istep  
        weight(k+knots) = weight(k)*eta  
        weight(k) = weight(k) - weight(k+knots)  
    end do  
    knots = 2*knots  
    istep = istep*ndim  
end do main

fint = 0.0_wp  
do k = 1 , knots  
    i = index(k)  
    fint = fint + weight(k)*table(i)  
end do

end function fint  

As I recall, I wrote wrappers to this function in order to be able to input the data in a more reasonable format. For example, for a five dimensional data set it is more natural to input the five rank-1 abscissa vectors and the rank-5 ordinate matrix. The disadvantage of this routine is that you have to stuff the ordinate matrix into a vector (as well as stuffing all the abscissa vectors into a single vector). This could also be an advantage in some cases, since Fortran arrays have a maximum rank. For Fortran 90, it was 7, while Fortran 2008 expanded this to 15 (the current Intel Fortran Compiler allows up to 31 as a non-standard extension). If you ever, for example, needed to interpolate 32-dimensional data (assuming you had enough RAM), you could do it with FINT without having to declare any rank-32 matrices. In any event, an example 5D wrapper for FINT is given here:

function fint_5d_wrapper(x,y,z,q,r,&  
                         xvec,yvec,zvec,qvec,&  
                         rvec,fmat) result(f)

use iso_fortran_env, only: wp => real64

implicit none

integer,parameter :: narg = 5

real(wp) :: f  
real(wp),intent(in) :: x,y,z,q,r  
real(wp),dimension(:),intent(in) :: xvec  
real(wp),dimension(:),intent(in) :: yvec  
real(wp),dimension(:),intent(in) :: zvec  
real(wp),dimension(:),intent(in) :: qvec  
real(wp),dimension(:),intent(in) :: rvec  
real(wp),dimension(:,:,:,:,:),intent(in) :: fmat

integer,dimension(narg) :: nent

nent(1) = size(xvec)  
nent(2) = size(yvec)  
nent(3) = size(zvec)  
nent(4) = size(qvec)  
nent(5) = size(rvec)

f = fint(narg,[x,y,z,q,r],nent,&  
    [xvec,yvec,zvec,qvec,rvec],&  
    reshape(fmat,[product(nent)]))

end function fint_5d_wrapper  

This works well enough, but note that it isn't very computationally efficient since we are creating temporary copies of the potentially large data arrays (including having to reshape a rank-5 matrix) every time we do an interpolation. While the logic of FINT is a bit hard to fathom, the actual equations are fairly simple (see here, for example). What we really need now is an object-oriented modern Fortran library for multidimensional linear interpolation. Stay tuned...

References

Feb 22, 2016

Aug 25, 2015

Intel Fortran Compiler 16.0

fortran-wheel

Intel just announced the availability of version 16.0 of the Intel Fortran Compiler (part of Intel Parallel Studio XE 2016). New features include:

  • Submodules (Fortran 2008)
  • IMPURE ELEMENTAL (Fortran 2008)
  • EXIT from BLOCK (Fortran 2008)
  • Full "Further Interoperability with C" implementation from TS29113 (Fortran 2015)
  • Improved coarray performance on Linux and Windows
  • On Windows, support for Visual Studio 2015

The new "C Descriptor" feature from Fortran 2015 looks pretty awesome, and finally plugs some of the holes in the C interoperability feature first introduced in Fortran 2003. It now allows C code to interact with Fortran pointers, allocatable variables, assumed shape variables, and CHARACTER(*) strings.

I used to be excited about submodules, which have the potential to reduce compilation cascades for very large projects. However, since Intel added the multi-processor compile option on Windows a few versions ago, that has been less bothersome for me. I'll probably try it out anyway, since it also might be useful for organizational purposes (splitting up very large modules into multiple submodules).

See also

  1. Intel Fortran Compiler 16.0 Release Notes
  2. What’s New in Intel Fortran 16.0

Jun 30, 2015

Next → Page 1 of 2