Is Fortran Memory-Safe?

The document ISO/IEC 24772-8 - Vulnerability descriptions for the programming language Fortran - currently under development by WG23, the ISO Work Group for Programming Language Vulnerabilities, recommends the following avoidance mechanisms related to parameter passing (clause 6.32), which includes argument aliasing:

6.32.2 Avoidance mechanisms for language users
Fortran software developers can avoid the vulnerability or mitigate its ill effects in the following ways. They can:

  • Use the avoidance mechanisms of ISO/IEC 24772-1:2019 clause 6.32.5.
  • Specify explicit interfaces by placing procedures in modules where the procedure is to be used in more than one scope, or by using internal procedures where the procedure is to be used in one scope only
  • Specify argument intents to allow further checking of argument usage.
  • Specify pure (or elemental) for procedures where possible for greater clarity of the programmer’s intentions.
  • Use a compiler or other tools to automatically create explicit interfaces for external procedures.
  • If available, use runtime checks against aliasing, at least during development.
  • Ensure that the result of a function is assigned, potentially through the use of static analysis tools or explicit runtime checks.

The first bullet point refers to this clause:

6.32.5 Avoiding the vulnerability or mitigating its effects
Software developers can avoid the vulnerability or mitigate its ill effects in the following ways. They can:

  • Use available mechanisms to label parameters as constants or with modes like in, out, or inout;
  • When a choice of mechanisms is available, pass small simple objects using call by copy;
  • When a choice of mechanisms is available and the computational cost of copying is tolerable, pass larger objects using call by copy;
  • When the choice of language or the computational cost of copying forbids using call by copy, then take safeguards to prevent aliasing:
    • Minimize side-effects of subprograms on non-local objects; when side-effects are coded, ensure that the affected non-local objects are not passed as parameters using call by reference;
    • To avoid unintentional aliasing effects, avoid using expressions or function calls as actual arguments; instead assign the result of the expression to a temporary local and pass the local;
    • Utilize tools or other forms of analysis to ensure that non-obvious instances of aliasing are absent:
  • Perform reviews or analysis to determine that called subprograms fulfil their responsibilities to assign values to all output parameters.

Drafts of the documents can be found in the WG23 Document Register.

1 Like

If the procedure argument is intent(in), passing an expression is fine, and if it is intent(out) or intent(in out) passing an expression is invalid and ideally will be detected by the compiler. So the advice seems relevant for arguments without declared intents, which one should try to minimize.

1 Like

Can any current Fortran compilers be configured to require intents? I recall that the old ELF90 compiler did by default.

G95 is not a “current” compiler, but with the -std=F option it prohibits non-F features, including arguments without intents. F was a subset of Fortran 95, like ELF90. For the code

module m
implicit none
contains
function f(x) result(y)
real :: x
real :: y
y = 2*x
end function f
end module m
!
program main
use m
implicit none
print*,f(3.2)
end program main

g95 -std=F xxf.f90 gives

In file xxf.f90:4

function f(x) result(y)
           1
Error: Dummy argument 'x' at (1) does not have an INTENT

and when x is declared intent(in) it says

function f(x) result(y)
         1
Error: Module procedure 'f' at (1) has no access specification

After declaring the function f public, it does compile and run the code

module m
implicit none
public :: f
contains
function f(x) result(y)
real, intent(in) :: x
real :: y
y = 2*x
end function f
end module m
!
program main
use m
implicit none
print*,f(3.2)
end program main

I used F and ELF90 to transition from Fortran 77 to Fortran 90. Compiler flags in gfortran or LFortran or flang to enforce a “good subset” would be nice, but people will disagree on what should be in the subset. F required the DIMENSION keyword to declare arrays, which I disliked.

1 Like

I’ve never used “aliasing” intentionally for in & out variables, but I wonder if the following code is invalid according to the Fortran standard? If so, is there any option for checking this with gfortran, ifort, etc, or do I need to check it manually with, e.g., c_loc() or loc()? (NAG seems to have an option for scalar variables but not for array?)

module test_m
contains
subroutine sub( inp, out )
    integer, intent(in)  :: inp(:)
    integer, intent(out) :: out(:)
    integer k
    !! if (loc(inp) == loc(out)) stop "aliasing"

    do k = 2, size(inp)
        out( k ) = inp( k - 1 ) * 100
    enddo
end
end module

program main
    use test_m
    implicit none
    integer a( 3 ), b( 3 )

    a(:) = [ 1, 2, 3 ]
    b(:) = 0
    call sub( inp = a, out = b )
    print *, "b = ", b   !! [0, 100, 200]

    a(:) = [ 1, 2, 3 ]
    call sub( inp = a, out = a )
    print *, "a = ", a   !! [1, 100, 10000]
end

$ gfortran -fcheck=all test.f90 && ./a.out
 b =            0         100         200
 a =            1         100       10000

Is the reason why no check option is provided for aliasing of arrays is that it is not straightforward to determine a possible “overlap” of two or more arrays that are actually accessed in a given routine (particularly with more subroutines calls in that routine)?

gfortran: -Waliasing

/app/example.f90:22:20:

   22 |     call sub( inp = a, out = a )
      |                    1
Warning: Same actual argument associated with INTENT(IN) argument 'inp' and INTENT(OUT) argument 'out' at (1)

If you remove the intents it goes undetected.

You can correct this by making a copy:

    call sub( inp = (a), out = a )    ! <-- N.b. the brackets

Array slicing on the other hand appears to inhibit the analysis:

    integer :: a( 6 )
    a(1:3) = [ 1, 2, 3 ]
    call sub( inp = a(1:3), out = a(3:5) )   ! Overlap (!), no warning
4 Likes

Thanks very much, this option (-Waliasing) seems very nice :slight_smile:

But because it is compile-time check (-W…), it seems not able to detect aliasing if pointers are used (like below). So it may be necessary to manually check the actual address of arrays (if really necessary to prevent aliasing). I remember I did such a manual check very very long time ago (only a few cases), but I had no case of doing that more recently (maybe because my coding style(?) changed somewhat…).

!! test.f90
module test_m
contains
subroutine sub( inp, out )
    integer, intent(in)  :: inp(:)
    integer, intent(out) :: out(:)
    integer k
    !! if (loc(inp) == loc(out)) stop "aliasing"

    do k = 2, size(inp)
        out( k ) = inp( k - 1 ) * 100
    enddo
end
end module

program main
    use test_m
    implicit none
    integer, target :: a( 3 )
    integer, pointer :: p(:)

    a(:) = [ 1, 2, 3 ]
    p => a(:)
    call sub( inp = a, out = p )
    print *, "a = ", a   !! [1, 100, 10000]
end

$ gfortran -fcheck=all -Waliasing test.f90 && ./a.out
 a =            1         100       10000
1 Like

Firstly, “aliasing” (a term not found in normative Standard text) itself is not prohibited in Fortran. The prohibition kicks in when a statement would cause the value of (whatever is associated with) a dummy argument to change through something other than that dummy in the statement. If you cannot guarantee that, you should not use (some forms of) argument association. If you don’t use argument association, you cannot fall foul of the “aliasing” restriction. You can also use a “safe” restricted form of argument association: for instance, no two dummy arguments of the same intrinsic type (and no derived type dummies).

Secondly, there seems to be the misunderstanding that some runtime checks are inherently impossible. They can be laborious to implement (in a software engineering sense), but no more than that. If you can see how a program could go wrong, so can the compiler. The probable reason that you don’t see compilers with more runtime checks is that people prefer a 10% runtime advantage to availability of checks that run N times slower (and back that preference up with purchasing decisions).

Thirdly, proving programs correct is the ultimate desideratum, and runtime checks don’t prove anything. Source-to-source tools that eliminate classes of vulnerabilities would be very useful, and some have appeared, but I think the vendors of these are struggling to retain users.

2 Likes

I think what programmers want is the ability to turn on these kinds of checks during the code development stage, and then turn them off for the production/optimized version of the program. Since these alias checks are not required by the standard, that’s asking a lot of compiler developers.

No, Fortran isn’t memory-safe. Assumed-size arrays allow one to do all the same evils as C pointers. Should they be used? No. Are they used extensively? Yes, and necessarily so in legacy Fortran projects like LAPACK.

There is a subset of the Fortran language which - in conjunction with certain implementation behavior - is relatively safe, but this isn’t different than C++. Unless you’re the DOD and you can pay a team to write a new spec for the subset you think is good (e.g. https://www.stroustrup.com/JSF-AV-rules.pdf), telling programmers to just avoid the dangerous features isn’t worth much.

3 Likes

You’re not alone in thinking assumed size arrays represent an insuperable problem, but did you check out the article referenced in the original post - or any of the ensuing discussion? There is no magic about assumed size arrays - bounds can be checked with slight run-time overhead, and there are compilers that do it.

I don’t think that’s the case. I don’t know a C compiler that can check all pointer usage. But for example the NAG compiler checks assumed-size arrays in all (?) cases.

Do you want to post an assumed-size array example that is not memory safe with NAG?

Checking the start and end addresses is not enough to determine effective aliasing, as strides must be taken into account. a(1:n:2) and a(2:n:4)` are not aliased for instance.

3 Likes

I suppose if you don’t care about ABI consistency at all, then sure, you can check both. It is possible to implement wide pointers in C - see CHERI for a hardware implementation - and do bounds checking. Similarly, you can replace array references with dope vectors and check everything. In both cases, you destroy any hope of interoperating with anything that isn’t compiled top to bottom with this toolchain.

So sure, the Fortran technically allows this, if you are fine with breaking everything in order to get it.

1 Like

In Fortran you have to use the same compiler anyway for Fortran code. At interface boundaries you should use bind(c). So the Fortran side can be safe, and checking assumed-size arrays is cheap.

Am I the only one who thinks these arguments re: memory safety are beside the point? The problem is the monolithic kernel architecture all modern operating systems in widespread use implement.

It seems that Rust enthusiasm has encouraged a new generation of developers to re-think current systems for improved security. There is a project to implement a microkernel with a POSIX interface in Rust that I am rather impressed by.

From a quick survey of the docs, they have implemented at the design level, all of the best practices recommended by security and operating systems research since the 1970s. Memory safety is moot when you don’t have untrusted code running at the kernel level.

This is the best effort I’ve seen that makes a serious attempt at mitigating memory safety and the security issues they imply, without necessitating a rewrite of over 50 years of software. Once GCC gets ported to this system, there shouldn’t be any problem with porting Fortran software either. The question is: what will the performance hit be due to the overhead of message passing?

I have worked on over 10 million lines of code where neither happens. I can mix GCC and Intel Fortran compilers as long as I link both runtime libraries, and assumed-size arrays are the way pre-2018 Fortran interoperates with C, but only because assumed-size arrays are implemented like C pointers in all the widely used compilers.

I understand this makes assumptions not guaranteed by the standard, but it is the basis for the majority of the Fortran usage in the world today. So sure, pure modern Fortran is safe if it’s compiled with NAG with checking enabled, but everything else isn’t safe. Given the size the of the “everything else”, maybe we need to be more cautious about claiming Fortran is safe.

Yes, Fortran can be used in an unsafe manner. It might also be that a lot of projects use it that way.

But in my opinions those projects should start using Fortran in a safe manner. For example, if NAG compiles your code, you can compile it in a safe manner. If you use assumed-size arrays for C interoperation, you have the option to upgrade it to bind(c), and it will be safe.

Finally, I think more compilers in the future will support safe options, not just NAG.

2 Likes

Do you have any insight on the performance impacts of “safe” Fortran? The biggest need for safety is at a trust boundary – ie. input from users or external systems. But once it is clear that the input is a valid element of the possible inputs, having code continue to check for validity is inefficient.

Fortran must be used in the Debug/Release combination:

  • Debug: safe, but slower
  • Release: maximum performance, but not safe

You can also consider ReleaseSafe, where all checks are enabled, but it is also optimized. This mode definitely has performance impacts.

So when you develop, use the Debug mode, and test it on all user inputs, ensuring there are no bugs. Then you can recompile in Release mode for maximum performance. If you encounter issues (segfaults or bad/random answers) in production in Release mode, then recompile in Debug mode and you’ll get a nice compiler error (ideally).

1 Like