Degenerate Conic

Algorithms • Modern Fortran Programming • Orbital Mechanics

Apr 24, 2016

Fortran & C Interoperability (Part 2)

C

Here's another example using the C interoperability features of modern Fortran. First introduced in Fortran 2003, this allows for easily calling C routines from Fortran (and vice versa) in a standard and portable way. Further interoperability features will also be added in the next edition of the standard.

For a Fortran user, strings in C are pretty awful (like most things in C). This example shows how to call a C function that returns a string (in this case, the dlerror function).

module get_error_module

use, intrinsic :: iso_c_binding

implicit none

private

public :: get_error

interface
    !interfaces to C functions
    function dlerror() result(error) &
    bind(C, name='dlerror')
    import
    type(c_ptr) :: error
    end function dlerror

    function strlen(str) result(isize) &
    bind(C, name='strlen')
    import
    type(c_ptr),value :: str
    integer(c_int) :: isize
    end function strlen
end interface

contains

function get_error() result(error_message)
!! wrapper to C function char *dlerror(void);

character(len=:),allocatable :: error_message

type(c_ptr) :: cstr
integer(c_int) :: n

cstr = dlerror() ! pointer to C string

if (c_associated(cstr)) then

    n = strlen(cstr) ! get string length

    block
        !convert the C string to a Fortran string
        character(kind=c_char,len=n+1),pointer :: s
        call c_f_pointer(cptr=cstr,fptr=s)
        error_message = s(1:n)
        nullify(s)
    end block

else
    error_message = ''
end if

end function get_error

end module get_error_module

First we define the bindings to two C routines so that we can call them from Fortran. This is done using the INTERFACE block. The main one is the dlerror function itself, and we will also use the C strlen function for getting the length of a C string. The bind(C) attribute indicates that they are C functions. The get_error function first calls dlerror, which returns a variable of type(c_ptr), which is a C pointer. We use c_f_pointer to cast the C pointer into a Fortran character string (a CHARACTER pointer variable with the same length). Note that, after we know the string length, the block construct allows us to declare a new variable s of the length we need (this is a Fortran 2008 feature). Then we can use it like any other Fortran string (in this case, we assign it to error_message, the deferred-length string returned by the function).

Of course, Fortran strings are way easier to deal with, especially deferred-length (allocatable) strings, and don't require screwing around with pointers or '\0' characters. A few examples are given below:

subroutine string_examples()

implicit none

!declare some strings:
character(len=:),allocatable :: s1,s2

!string assignment:
s1 = 'hello world' !set the string value
s2 = s1 !set one string equal to another

!string slice:
s1 = s1(1:5) !now, s1 is 'hello'

!string concatenation:
s2 = s1//' '//s1 ! now, s2 is 'hello hello'

!string length:
write(*,*) len(s2) ! print length of s2 (which is now 11)

!and there are no memory leaks,
!since the allocatables are automatically
!deallocated when they go out of scope.

end subroutine string_examples

See also

Apr 09, 2016

C++ vs Fortran (Part 3)

matrix

Built-in high-level support for arrays (vectors and matrices) using a very clean syntax is one of the areas where Fortran really shines as a programming language for engineering and scientific simulations. As an example, consider matrix multiplication. Say we have an M x K matrix A, a K x N matrix B, and we want to multiply them to get the M x N matrix AB. Here's the code to do this in Fortran:

AB = matmul(A,B)

Now, here's how to do the same thing in C or C++ (without resorting to library calls) [1]:

for (int i = 0; i < M; i++) {
    for (int j = 0; j < N; j++) {
        AB[i][j]=0;
        for (int k = 0; k < K; k++) {
            AB[i][j] += A[i][k] * B[k][j];
        }
    }
}

MATMUL is, of course, Fortran's built-in matrix multiplication function. It was added to the language as part of the Fortran 90/95 standards which dramatically upgraded the language's array-handling facilities. Later standards also added additional array features, and Fortran currently contains a wide range of intrinsic array functions:

Routine Description
ALL True if all values are true
ALLOCATED Array allocation status
ANY True if any value is true
COUNT Number of true elements in an array
CSHIFT Circular shift
DOT_PRODUCT Dot product of two rank-one arrays
EOSHIFT End-off shift
FINDLOC Location of a specified value
IPARITY Exclusive or of array elements
IS_CONTIGUOUS Test contiguity of an array
LBOUND Lower dimension bounds of an array
MATMUL Matrix multiplication
MAXLOC Location of a maximum value in an array
MAXVAL Maximum value in an array
MERGE Merge under mask
MINLOC Location of a minimum value in an array
MINVAL Minimum value in an array
NORM2 L2 norm of an array
PACK Pack an array into an array of rank one under a mask
PARITY True if number of elements in odd
PRODUCT Product of array elements
RESHAPE Reshape an array
SHAPE Shape of an array or scalar
SIZE Total number of elements in an array
SPREAD Replicates array by adding a dimension
SUM Sum of array elements
TRANSPOSE Transpose of an array of rank two
UBOUND Upper dimension bounds of an array
UNPACK Unpack an array of rank one into an array under a mask

As an example, here is how to sum all the positive values in a matrix:

b = sum(A, mask=(A>0.0))

In addition to the array-handling functions, we can also use various other language features to make it easier to work with arrays. For example, say we wanted to convert all the negative elements of a matrix to zero:

where (A<0.0) A = 0.0

Or, say we want to compute the dot product of the 1st and 3rd columns of a matrix:

d = dot_product(A(:,1),A(:,3))

Or, replace every element of a matrix with its sin():

A = sin(A)

That last one is an example of an intrinsic ELEMENTAL function, which is one that can operate on scalars or arrays of any rank. The assignment is done for each element of the array (and can potentially be vectored by the compiler). We can create our own ELEMENTAL functions like so:

elemental function cubic(a,b,c) result(d)
real(wp),intent(in) :: a,b,c
real(wp) :: d
d = a + b**2 + c**3
end function cubic

Note that the inputs and output of this function are scalars. However, since it is ELEMENTAL, it can also be used for arrays like so:

real(wp) :: aa,bb,cc,dd
real(wp),dimension(10,10,10) :: a,b,c,d
!...
dd = cubic(aa,bb,cc) ! works on these
d = cubic(a,b,c) ! also works on these

The array-handling features of Fortran make scientific and engineering programming simpler and less error prone, since the code can be closer to the mathematical expressions, as well as making vectorization by the compiler easier [2]. Here is an example from the Fortran Astrodynamics Toolkit, a vector projection function:

pure function vector_projection(a,b) result(c)

implicit none

real(wp),dimension(:),intent(in) :: a
!! the original vector
real(wp),dimension(size(a)),intent(in) :: b
!! the vector to project on to
real(wp),dimension(size(a)) :: c
!! the projection of a onto b

if (all(a==0.0_wp)) then
    c = 0.0_wp
else
    c = a * dot_product(a,b) / dot_product(a,a)
end if

end function vector_projection

Line 15 is the vector projection formula, written very close to the mathematical notation. The function also works for any size vector. A similar function in C++ would be something like this:

inline std::array<double,3>
vector_projection(const std::array<double,3>& a,
const std::array<double,3>& b)
{
    if (a[0]==0.0 & a[1]==0.0 & a[2]==0.0){
        std::array<double,3> p = {0.0, 0.0, 0.0};
        return p;
    }
    else{
        double aa = a[0]*a[0]+a[1]*a[1]+a[2]*a[2];
        double ab = a[0]*b[0]+a[1]*b[1]+a[2]*b[2];
        double abaa = ab / aa;
        std::array<double,3>
        p = {a[0]*abaa,a[1]*abaa,a[2]*abaa};
        return p;
    }
}

Of course, like anything, there are many other ways to do this in C++ (I'm using C++11 standard library arrays just for fun). Note that the above function only works for vectors with 3 elements. It's left as an exercise for the reader to write one that works for any size vectors like the Fortran one (full disclosure: I mainly just Stack Overflow my way through writing C++ code!) C++'s version of dot_product seems to have a lot more inputs for you to figure out though:

double ab = std::inner_product(a.begin(),a.end(),b.begin(),0.0);

In any event, any sane person using C++ for scientific and engineering work should be using a third-party array library, of which there are many (e.g., Boost, EIGEN, Armadillo, Blitz++), rather than rolling your own like we do at NASA.

References

  1. Walkthrough: Matrix Multiplication [MSDN]
  2. M. Metcalf, The Seven Ages of Fortran, Journal of Computer Science and Technology, Vol. 11 No. 1, April 2011.
  3. My Corner of the World: C++ vs Fortran, September 07, 2011

Apr 05, 2016

Atom + Fortran

dock2

This newfangled Atom hipster text editor is really a nice editor for Fortran when you install these two plugins:

There are tons of other packages too. For example, indent-helper is a must, because every sane person knows that ='s and ::'s should always be aligned.

For many years, I've used TextWrangler by Bare Bones Software (which is the free version of their more powerful BBEdit). Just having the Fortran linter (see below) is enough to make me switch. I suppose with the right combination of plugins, I could use it as a full-fledged IDE, but I haven't really tried to do that yet.

atom

Maybe one day @szaghi will write a FoBiS plugin for Atom. Unfortunately, I think he's totally committed to vi.

See also

Apr 05, 2016

Linked Lists

linked-list

So, I want to have a basic linked list manager, written in modern Fortran (2003/2008). Of course, Fortran provides you with nothing like this out of the box, but it does provide the tools to create such a thing (within reason). Pointers (introduced in Fortran 90) allow for the creation of dynamic structures such as linked lists. In Fortran, you can do quite a lot without having to resort to pointers (say, compared to C, where you can't get away from them if you want to do anything nontrivial), but in this case, we need to use them. With the addition of unlimited polymorphic variables in Fortran 2003, we can now also create heterogeneous lists containing different types of variables, which is quite handy. There are some good Fortran linked-list implementations out there (see references below). But none seemed to do exactly what I wanted. Plus I wanted to learn about this stuff myself, so I went ahead and started from scratch. My requirements are that the code:

  • Accept any data type from the caller. I don't want to force the caller to stuff their data into some standard form, or make them have to extend an abstract derived type to contain it.
  • Accept data that may perhaps contain targets of pointers from other variables that are not in the list. This seems useful to me, but is an aspect that is missing from the implementations I have seen, as far as I can tell. If the data is being pointed to by something externally, doing a sourced allocation to create a copy is not acceptable, since the pointers will still be pointing to the original one and not the copy.
  • Allow for the list to manage the destruction of the variable (deallocation of the pointer, finalization if it is present), or let the user handle it. Perhaps the list is being used to collocate and access some data, but if the list goes out of scope, the data is intended to remain.
  • In general, limit the copying of data (some entries in the list may be very large and it is undesirable to make copies).
  • Allow the key to be an integer or string (or maybe other variable types as well)

For lack of a better name, I've called the resultant library FLIST (it's on GitHub). It's really just an experiment at this point, but I think it does everything I need. The node data type used to construct the linked list is this:

type :: node
    private
    class(*),allocatable :: key
    class(*),pointer :: value => null()
    logical :: destroy_on_delete = .true.
    type(node),pointer :: next => null()
    type(node),pointer :: previous => null()
    contains
    private
    procedure :: destroy => destroy_node_data
end type node

The data in the node is a CLASS(*),POINTER variable (i.e, a pointer to an unlimited polymorphic variable). This will be associated to the data that is added to the list. Data can be added as a pointer (in which case no copying is performed), or added as a clone (where a new instance of the node data is instantiated and a copy of the input data is made). If the data is added as a pointer, the user can also optionally specify if the data is to be destroyed when the list is destroyed or goes out of scope (or if the item is deleted from the list).

The key is also an unlimited polymorphic variable (in the user-accessible API, keys are limited to integers, character strings, or extensions of an abstract key_class):

type,abstract,public :: key_class
    contains
    procedure(key_equal_func),deferred :: key_equal
    generic :: operator(==) => key_equal
end type key_class

The key types have to be limited, since there has to be a way to check for equality among keys (the abstract key_class has a deferred == operator that must be specified). The Fortran SELECT TYPE construct is used to resolve the polymorphic variables in order to check for equality among keys.

A simple example use case is shown below. Here we have some derived type gravity_model that is potentially very large, and is initialized by reading a data file. The subroutine takes as input a character array of file names to read, loads them, and appends the resultant models to the list_of_models.

subroutine add_some_models(files,list_of_models)

use linked_list_module
use gravity_model_module

implicit none

character(len=:),dimension(:),intent(in) :: files
type(list),intent(inout) :: list_of_models

integer :: i
type(gravity_model),pointer :: g

do i=1,size(files)
    allocate(g)
    call g%initialize(files(i))
    call list_of_models%add_pointer(files(i),g)
    nullify(g)
end do

end subroutine add_some_models

In this example, all the models are allocated in the subroutine, and then added as pointers to the list (the file name is used as the key). When list_of_models goes out of scope, the models will be deallocated (and finalized if gravity_model contains a finalizer). A model can be removed from the list (which will also trigger finalization) using the key, like so:

call list_of_models%remove('blah.dat')

More complex use cases are also possible (see the code for more details). As usual, the license is BSD, so if anybody else finds it useful, let me know.

See also

  1. T. Dunn, fortran-linked-list [GitHub]
  2. T. Degawa, LinkedList [GitHub]
  3. libAtoms/QUIP [GitHub]
  4. N. R. Papior, fdict [GitHub]
  5. C. MacMackin, FIAT [GitHub]
  6. J. R. Blevins, A Generic Linked List Implementation in Fortran 95, ACM Fortran Forum 28(3), 2–7, 2009.

Apr 03, 2016

C++ vs Fortran (Part 2)

Here is some C++ code (from actual NASA software):

aTilde[ 0] = aTilde[ 1] = aTilde[ 2] =
aTilde[ 3] = aTilde[ 4] = aTilde[ 5] =
aTilde[ 6] = aTilde[ 7] = aTilde[ 8] =
aTilde[ 9] = aTilde[10] = aTilde[11] =
aTilde[12] = aTilde[13] = aTilde[14] =
aTilde[15] = aTilde[16] = aTilde[17] =
aTilde[18] = aTilde[19] = aTilde[20] =
aTilde[21] = aTilde[22] = aTilde[23] =
aTilde[24] = aTilde[25] = aTilde[26] =
aTilde[27] = aTilde[28] = aTilde[29] =
aTilde[30] = aTilde[31] = aTilde[32] =
aTilde[33] = aTilde[34] = aTilde[35] = 0.0;

Here is the same code translated to Fortran:

aTilde = 0.0

😀

References

Mar 14, 2016

Namelist Error Checking

Fortran namelists are a quick and dirty way of reading and writing variables to and from a file. It is actually the only high-level file access feature built into the Fortran language, in the sense of being able to read and write a complex formatted file with one line of code. Nowadays, I would recommend against using this feature since the format is not really a standard and varies from compiler to compiler, and there aren't good parsers available for other languages (with the notable exception of Python). There are better configuration file formats available today such as JSON. However, namelists can still be encountered in legacy applications, and may still be useful to the lazy programmer.

One of the problems with namelists is that all the variables in the file have to correspond exactly in name, type, rank, and size to variables declared in your code. Syntax errors in the file are not easily detected and a failed read due to an unexpected variable will usually just return a non-zero status code that isn't really much help in diagnosing the problem.

However, there is a way to output the line where the failure occurred on a namelist read, which can be quite useful for debugging. Say your code is expecting a namelist containing three real variables a, b, and c. However, the file contains the unexpected variable d like so:

&my_namelist
 a = 1.0,
 b = 2.0,
 d = 3.0,
 c = 4.0
/

Now consider the following Fortran code to read it:

program namelist_test

use iso_fortran_env, wp => real64

implicit none

real(wp) :: a,b,c ! namelist variables
integer :: istat,iunit
character(len=1000) :: line

namelist /my_namelist/ a,b,c

open(newunit=iunit,file='my_namelist.nml',&
    status='OLD')

read(iunit, nml=my_namelist, iostat=istat)

if (istat/=0) then
    backspace(iunit)
    read(iunit,fmt='(A)') line
    write(error_unit,'(A)') &
        'Invalid line in namelist: '//trim(line)
end if

close(iunit)

end program namelist_test

The READ statement will fail with a non-zero istat code. Then we simply use the BACKSPACE function, which moves the file position back one record (the record where the read failed). Then we can simply read this line and print it. This code produces the following error message:

 Invalid line in namelist: d = 3.0,

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

Dec 28, 2015

DDEABM

ddeabm

DDEABM is variable step size, variable order Adams-Bashforth-Moulton PECE solver for integrating a system of first order ordinary differential equations [1-2]. It is a public-domain code originally developed in the 1970s-1980s, written in FORTRAN 77, and is available from Netlib (as part of the SLATEC Common Mathematical Library). DDEABM is primarily designed to solve non-stiff and mildly-stiff differential equations when derivative evaluations are expensive, high accuracy results are needed or answers at many specific points are required. It is based on the earlier ODE/STEP/INTRP codes described in [3-4].

DDEABM is a great code, but like many of the greats of Fortran, it seems to have been frozen in amber for 30 years. There are a couple of translations into other programming languages out there such as IDL and Matlab. It is also the ancestor of the Matlab ode113 solver (indeed, they were both written by the same person [5]). But, it looks like poor Fortran users have been satisfied with using it as is, in all its FORTRAN 77 glory.

So, I've taken the code and significantly refactored it to bring it up to date to modern standards (Fortran 2003/2008). This is more than just a conversion from fixed to free-form source. The updated version is now object-oriented and thread-safe, and also has a new event finding capability (there is a version of this code that had root-finding capability, but it seems to be based on an earlier version of the code, and also has some limitations such as a specified maximum number of equations). The new event finding feature incorporates the well-known ZEROIN algorithm [6-7] for finding a root on a bracketed interval. Everything is wrapped up in an easy-to-use class, and it also supports the exporting of intermediate integration points.

The new code is available on GitHub and is released under a permissive BSD-style license. It is hoped that it will be useful. There are some other great ODE codes that could use the same treatment (e.g. DLSODE/DVODE from ODEPACK, DIVA from MATH77, and DOP853 from Ernst Hairer).

References

  1. L. F. Shampine, H. A. Watts, "DEPAC - Design of a user oriented package of ode solvers", Report SAND79-2374, Sandia Laboratories, 1979.
  2. H. A. Watts, "A smoother interpolant for DE/STEP, INTRP and DEABM: II", Report SAND84-0293, Sandia Laboratories, 1984.
  3. L. F. Shampine, M. K. Gordon, "Solving ordinary differential equations with ODE, STEP, and INTRP", Report SLA-73-1060, Sandia Laboratories, 1973.
  4. L. F. Shampine, M. K. Gordon, "Computer solution of ordinary differential equations, the initial value problem", W. H. Freeman and Company, 1975.
  5. L. F. Shampine and M. W. Reichelt, "The MATLAB ODE Suite" [MathWorks].
  6. R. P. Brent, "An algorithm with guaranteed convergence for finding a zero of a function", The Computer Journal, Vol 14, No. 4., 1971.
  7. R. P. Brent, "Algorithms for minimization without derivatives", Prentice-Hall, Inc., 1973.

Nov 13, 2015

Fortran + LLVM

llnl

Good news everyone! The US government just announced that it has reached an agreement with NVIDIA to produce an open source Fortran front-end for the LLVM compiler infrastructure. It will be based on the existing commercial Portland Group compiler (NVIDIA purchased the Portland Group a couple of years ago). Source code for the Fortran front-end is expected to be available in late 2016. From the announcement:

The project is being spearheaded by the Lawrence Livermore, Sandia and Los Alamos national laboratories in response to the need for a robust open-source Fortran solution to complement and support the burgeoning use of LLVM and the CLANG C++ compiler in the HPC community. Large HPC applications, such as those developed by the NNSA Laboratories, are often built on mixed-language modules, and require a common compiler infrastructure that supports both C/C++ and Fortran. Fortran also remains widely used in the broader scientific computing community, supporting simulation science to advance national security, medicine, energy, climate and basic science missions.

Does Fortran support for LLVM mean that we'll eventually be able to have Fortran code running on our iPads? Only time will tell...

See also

← Previous Next → Page 6 of 11