Does a SUBROUTINE know its own name?

Hi,

I would like to make a module with subroutines for prognostic messages and it would be nice if the prognostic routine would know who is calling. Something like:

SUBROUTINE John()
  REAL, PARAMETER :: x = 3.1415
  CALL Prognostic_ShowValue(x)
END SUBROUTINE John

where calling subroutine John would result in a message “John says that x = 3.1415”

Of course, I can add a name tag to all my subroutines and pass that name to the subroutine too, but that may not be necessary. How to accomplish this?

Regards,

Arjan

1 Like

There were recent additions to the standard to allow you to get things like compiler name and version but I don’t know about subroutine name. There is a pre-processor macro (FILE) that is set by some compilers that you can use but that means you have to enable preprocssing for your source files (either explicitly or just rename your files to have a .F or .F90 file extension.

Here is an C include file I use mimic the C assert function in source files. It just calls a user supplied subroutine called assert but passes the file name and the current line number (LINE)

  
#ifdef __GFORTRAN__
#define ASSERT(x) call assert(x,"x",__FILE__,__LINE__)
#define ERROR_ABORT(x,y) call assert(x,"x",__FILE__,__LINE__,y)
#else
#define ASSERT(x) call assert(x,#x,__FILE__,__LINE__)
#define ERROR_ABORT(x,y) call assert(x,#x,__FILE__,__LINE__,y)
#endif

in your Fortran code just add

#include asserts.h

ASSERT (X==0.0)

etc. and the preprocessor will insert a call to your assert subroutine.

You could try func or FUNCTION and see if they work Standard Predefined Macros (The C Preprocessor)

Unfortunately, no there is not a language intrinsic, portable way to get the currently executing function or subroutine name.

Thanks. Seems like a nontrivial thing.

We have a proposal in the works for an intrinsic function that returns the current program unit name, usable in constant expressions. At least among the committee members who discussed this at the February meeting (JoR subgroup), we all agreed that this would be a handy thing. This proposal hasn’t yet been fleshed out, but I expect it will be for the June meeting.

18 Likes

This would be very helpful. Over 2500 character constants exist in our newly released library, whose sole purpose is to achieve this functionality manually and painfully (because it involves copy-pasting unit names in strings). Having line and file indicators similar to __LINE__ and __FILE__ would also be very helpful. We have used these two macros over 5,500 times in this library. The portability of these FPP extensions is another issue that we had to invest some thinking to bypass.

1 Like

Yes, __LINE__ and __FILE__ are part of our accepted proposal for preprocessor support.

1 Like

I hate counting underscores.

2 Likes

In C++20 they got rid of macros for this purpose: https://en.cppreference.com/w/cpp/utility/source_location

3 Likes

A related feature provided by some compilers allows generating a stacktrace, optionally exiting. Where supported this is a very useful diagnostic tool. Is any traceback function included in the proposal?

ifx(1) has tracebackqq(), for example:

program testit
implicit none
   write(*,*)'commence'
   call a()
   write(*,*) 'finish'
contains

subroutine a()
   call b()
end subroutine a

subroutine b()
use ifcore
   call tracebackqq(string="Done with pass 1", user_exit_code=-1)
end subroutine b

end program testit
ifx -O0 -g -traceback tryit.f90 -o tryit && ./tryit
 commence
Done with pass 1
Image              PC                Routine            Line        Source             
tryit              00000000004052AE  b                          15  main.f90
tryit              000000000040526D  a                          10  main.f90
tryit              0000000000405201  testit                      5  main.f90
tryit              000000000040518D  Unknown               Unknown  Unknown
libc-2.31.so       0000146656671083  __libc_start_main     Unknown  Unknown
tryit              00000000004050AE  Unknown               Unknown  Unknown
 finish

ifx’s tracebackqq dates back to Digital Visual Fortran. A stack trace feature is not being proposed for the standard.

It is a shame. Once people can easily access the procedure names a stack trace is so useful people will implement it with a linked list or some other pop/push, probably conditionally and far less efficiently than the compiler/loader could, creating a lot of duplicate efforts.

I already have seen codes that manually pass the name of the caller procedure to the callee to provide this. I would guess there were be several fpm(1) projects as soon as the feature is in Fortran to create libraries for generating a stack trace using the proposed feature.

It does seem many Fortran compilers provide at least an optional backtrace ability; albeit often only at low optimization and with symbol tables available. That indicates it might not be too big an ask to make it standard at least in some “conditionally available” way; but most (all?) of the system interface procedures like date_and_time are only optionally required to fully function.

See Also:

2 Likes

Symbolic backtraces require a lot of information to be added to the executable in ways that tend to be implementation-specific. I know that for DVF we had to invent this out of whole cloth, as the MS toolchain had no concept. Yes, if you are in the debugger you can leverage debug info for this, but not generally for production code.

Yes; but having a method of doing a stacktrace is important enough that the first four compilers I surveyed all had a method of doing it. That seems to indicate it would not be an unreasonable burden to add it as an optional standard interface; and that is is valuable to do so. As soon as ERROR STOP was introduced the implementations I saw produced a trace much like is common with abort(). That fact that it was implemented from whole cloth for DVF suggests it is important enough to a programming language
to make available even if it is difficult, it seems. So many things are implemented like this by nearly every compiler including something like POSIX interfaces that always hold people back from using Fortran. It will at least be better than it was to have file, line number, and procedure name available; and it took decades to just get a standard method for obtaining the date and time (and timezone is still not handled in a standard way) so glad to see some forward movement. But it is so natural to do so that once the constants are available people will construct ways to get a backtrace with them; and there will likely be a lot of duplicate code generated. Anyone thinking about using the 2023 features is almost immediately going to be figuring out how to use it to get a stack trace.

1 Like