Underscore at the end of a Fortran name

Quick question: Can there be problems when a Fortran name ends with an underscore like example_var_?
I was told to avoid underscores at the end of names, because compilers might add underscores internally, but I couldn’t find anything about this. Even in the j3-fortran document (side question, how do you call this document normally?) there is an example with a trailing underscore (6.2.2 / R603) and stdlib uses such variables, too. So I assume it is safe to name variables like this, but maybe it was problematic in an earlier version of Fortran?

1 Like

No, it is safe to do so. Fortran does not allow underscores at the beginning of a name, but any trailing underscores the compiler may add should not be visible on the Fortran side. (This is a different matter for C, where names internal or special to the compiler may have a bunch of underscores and these would be visible on the C side)

2 Likes

Okay, since interoperability with C is a common thing, is it still safe to use trailing underscores in Fortran source code or could it result in problems with the C code?

Not really, Fortran symbols usually get additionally mangled with the module name, unless you add bind(c). You could try to guess the symbol name from C for non-module procedures, but again this is not guaranteed to work unless they have bind(c).

1 Like

I don’t think there is any problem with doing so and often create a local variable with the name of an optional argument appended by an underscore, for example

if (present(foo)) then
   foo_ = foo
else
   foo_ = foo_default
end if
! use foo_ in the rest of the procedure
1 Like

What do you mean by ‘guess the symbol name from C’? I don’t want to try to hack around C-Fortran interoperability. I just want to be 100% sure that nothing unexpected will ever happen, caused by a trailing underscore.
I use them a lot, too (e.g. result_). But when it comes to teaching Fortran, I have to be extra careful, because errors I teach multiply…

Precisely, in the old days, best forgotten, you had to guess the name mangling (one underscore, two underscores, all capitals) and use the result on the C side. But with the bind(C) facility that is no longer required.

1 Like

I don’t think this will cause issues for local variables.

You could try to inspect your object files with nm and look whether you actually find some symbols which might resemble the result_ variable from your source code. I found it quite insightful to see which symbols are actually exported from a module and which are not visible or just heavily mangled.

4 Likes

TL;DR: the answer is no.

No worries here, you can use trailing underscores as needed in your code.

1 Like

Thanks for the tip about nm, which I decided to experiment with. For the the code

module twice_mod
implicit none
private
integer :: nobs, ncol
real, parameter :: pi = 3.14
private :: twice_scalar, thrice, ncol
public :: twice, twice_vec, quad, pi, nobs
interface twice
   module procedure twice_vec
end interface twice
contains
function twice_scalar(i) result(j)
implicit none
integer, intent(in) :: i
integer             :: j
j = 2*i
end function twice_scalar
!
function twice_vec(i) result(j)
implicit none
integer, intent(in) :: i(:)
integer             :: j(size(i))
j = 2*i
end function twice_vec
!
function thrice(i) result(j)
implicit none
integer, intent(in) :: i
integer             :: j
j = 3*i
end function thrice
!
function quad(i) result(j)
implicit none
integer, intent(in) :: i
integer             :: j
j = 4*i
end function quad
end module twice_mod

nm run on the .o file created by gfortran gives

0000000000000000 b .bss
0000000000000000 d .data
0000000000000000 p .pdata
0000000000000000 r .rdata$zzz
0000000000000000 t .text
0000000000000000 r .xdata
0000000000000000 B __twice_mod_MOD_ncol
0000000000000004 B __twice_mod_MOD_nobs
0000000000000000 T __twice_mod_MOD_quad
0000000000000021 t __twice_mod_MOD_thrice
00000000000001a5 t __twice_mod_MOD_twice_scalar
0000000000000045 T __twice_mod_MOD_twice_vec

It appears that public procedures such as quad and twice_vec are labeled T and the private ones such as thrice and twice_scalar are labeled t. Both ncol and nobs are labeled B, although only nobs is public. The named constant pi does not appear.

keep in mind that the name mangling is compiler dependent:

maws01 ➜  /tmp ifort -c test.f90 
maws01 ➜  /tmp nm test.o
0000000000000000 T twice_mod._
0000000000000004 C twice_mod_mp_ncol_
0000000000000004 C twice_mod_mp_nobs_
0000000000000180 T twice_mod_mp_quad_
0000000000000170 T twice_mod_mp_thrice_
0000000000000010 T twice_mod_mp_twice_scalar_
0000000000000020 T twice_mod_mp_twice_vec_
maws01 ➜  /tmp gfortran -c test.f90
maws01 ➜  /tmp nm test.o
0000000000000000 B __twice_mod_MOD_ncol
0000000000000004 B __twice_mod_MOD_nobs
0000000000000000 T __twice_mod_MOD_quad
0000000000000019 t __twice_mod_MOD_thrice
0000000000000183 t __twice_mod_MOD_twice_scalar
0000000000000035 T __twice_mod_MOD_twice_vec

If you’re worried about C, Fortran has very specific rules about what happens when a global symbol has the BIND(C) attribute (Fortran name is downcased, no Fortran-specific decoration). If you need further control, add NAME=, in which case the string you give is treated exactly as if you had specified that in the “companion C processor”.

1 Like