Cpp (C preprocessor) tricks

Among other things, the C preprocessor can be used for various syntactic sugars. For instance in this recent thread 2 of them have given:

Turning the F2023 conditional expressions into something more fortranic:

#define _if_ (
#define _then_ ?
#define _else_ :
#define _endif_ )

value = _if_ condition _then_ truexpr _else_ falsexpr _endif_
! turns into
value = ( condition ? truexpr : falsexpr )

Another approach to just make the conditional expression look like a function:

#define _condexpr_ 

value = _condexpr_( condition ? truexpr : falsexpr )

@septc gave his trick to give manage default value of optional arguments:

#ifdef __GFORTRAN__
#define _setopt_(x,val) x = val; if (present(x/**/_)) x = x/**/_
#else
#define _setopt_(x,val) x = val; if (present(x##_)) x = x##_
#endif

subroutine somesub(somearg_)
integer, optional :: somearg_
integer :: somearg

_setopt_(somearg, 10)
! turns into 
somearg = 10; if (present(somearg_)) somearg = somearg_

I was also thinking about the built-in declaration of the index of a DO statement, as well as the loop body being an implicit block:

#define _do_blk_(type,i,m1,m2,m3) block; type :: i; do i = m1, m2, m3 ; block
#define _end_do_blk_ end block; end do; end block

_do_blk_(integer(int64), j, 1, n, 1)
    real :: v
    v = j
    print*, v
_end_do_blk_
! turns into (splitting some lines):
block
   integer(int64) :: i
   do i = 1, n, 1 ; block
       real :: v
       v = j
       print*, v
   end block ; end do
end block

I am definetly not a cpp-master, and it could be fun to post your various cpp tricks here !

2 Likes

It will be good if readers here on this forum whoā€™re also members of J3 in some form or other, like @everythingfunctional , @sblionel , @gak , can keep a close eye on threads like this toward the needs and practices by Fortranners that shall be considered closely during the development of the supposed Fortran 202Y work list item on standard support for preprocessing in Fortran.

1 Like

I have seen a lot of preprocessing. I use the prep(1) preprocessor myself but
I have encountered some unusual ā€œtricksā€ along the way. One of the more
unusual ones is having multiple file types (C, Fortran, docs, ā€¦) in a single file
and then having a makefile use commands to separate the parts like

cpp -D_MD_CODE FILE|pandoc >doc.html
cpp -D_C_CODE FILE FILE.c
cpp -D_F_CODE FILE FILE.f90

or have little associated files like to extract the C part a little file ā€œFILE.cā€:

#define _C_CODE
#include "FILE"

because of a strong preference to keep everything related to a procedure in
a single file. The file then looks something like this ā€¦

#ifdef _MD_CODE_
This is my documentation written
in markdown.
#endif

#ifdef _C_CODE_
/*
Here are some C procedures that are used along with ISO_C_BINDING
by the Fortran code
*/
#endif

#ifdef _F_CODE_
!! Fortran code
#endif

Less exotic are things like having

  • #include files that turn debugging on and off with custom print macros
  • to be used for templating where the common code is in an include file and
    type definitions are in the main file
  • predefined constants, although now done relatively easily with a module instead
  • abbreviations used for commonly used lines or to standardize usage
  • defining macros using a standard convention that are pre-defined by various
    platforms in an ad-hoc manner so they are easier and more reliably used
  • just for the ability to have free-format blocks of comments
  • to provide metadata in a central file

A little example of templating with preprocessing and include files

! combined with #include for templating
subroutine a_32()
integer,parameter :: wp=kind(0.0)
#include "a"
end subroutine a_32
subroutine a_64()
integer,parameter :: wp=kind(0.0d0)
#include "a"
end subroutine a_64

Here is an attempt at showing some of the uses I have made of cpp(1) in the past
or have seen along the way. These are illustrations, not advocacy!

/* pick one */
#undef DEBUGON
#define DEBUGON

/* Constants */
#define __PI__ 3.141592653589793238462643383279502884197169399375105820974944592307d0

/* Debug I/O */
#ifdef DEBUGON
#define DEBUG print '(*(g0,":"))',"<DEBUG>",__TIMESTAMP__,"FILE",__FILE__,"LINE",__LINE__
#else
#define DEBUG !
#endif

/* Abbreviations */

#define __ISO_TYPES__ use,intrinsic :: iso_fortran_env, only : int8, int16, int32, int64, real32, real64, real128
#define __ISO_IO__    use,intrinsic :: iso_fortran_env, only : iostat_eor, iostat_end, stdin=>input_unit, stderr=>error_unit, stdout=>output_unit
#define __ISO_COMPILER__ use,intrinsic :: iso_fortran_env, only : compiler_options, compiler_version
#define __ISO__ use,intrinsic :: iso_fortran_env, only : sp=>real32,dp=>real64 
/*Standardize pre-defined macros*/
#define  _UNIX        1
#define  _MS_WINDOWS  2
#define  _APPLE       3
#define  _CYGWIN      4
#define  _UNKNOWN     999
#ifdef __unix
#define __IFON__ _UNIX
#endif
#ifdef _WIN32
#define __IFON__ _MSWINDOWS
#endif
#ifdef __APPLE__
#define __IFON__ _APPLE
#endif
#ifdef __CYGWIN__
#define __IFON__ _CYGWIN
#endif
#ifndef __IFON__
#define __IFON__ _UNKNOWN
#endif
/* Standardize pre-defined compiler ID */

#define __INTEL_COMP 1
#define __GFORTRAN_COMP 2
#define __NVIDIA_COMP 3
#define __NAG_COMP 4
#define __UNKNOWN_COMP 9999

#define REAL128 0
#ifdef __INTEL_COMPILER
#   define __COMPILER__ __INTEL_COMP
#elif __GFORTRAN__ == 1
#   define __COMPILER__ __GFORTRAN_COMP
#elif __NVCOMPILER
#   define REAL128 1
#   define __COMPILER__ __NVIDIA_COMP
#else
#   define __COMPILER__ __UNKNOWN_COMP
#   warning  NOTE: UNKNOWN COMPILER
#endif
/* Metadata */
#define PROGRAM_NAME "printenv"
#define VERSION "1.0.0"
#define AUTHORS "David MacKenzie", "Richard Mlynarik"
#define LICENSE "MIT"

program testit
/*
  It is a lot easier to maintain free-format text blocks
  than it is to maintain Fortran comments with a exclamation
  in front of every line, even if your favorite editor 
  supports editing Fortran comment blocks
*/
__ISO_TYPES__
__ISO_IO__
__ISO__
implicit none
real :: A=100.0
! constants
real,parameter :: PI= __PI__
! compiled on __IFON__ 
#if __IFON__ == _APPLE
   write(*,*)'An Apple a Day keeps Dr. DOS away!'
#endif
#if __IFON__ == _UNIX
   write(*,*)'Well, that takes some brass!'
#endif
#if __IFON__ == _CYGWIN
   write(*,*)'An application or an OS?'
#endif
#if __IFON__ == _UNKNOWN
   write(*,*)'Where am I?'
#endif
DEBUG , "got here!"
! print more debug values
DEBUG ,"A",A
write(*,*) __IFON__
write(*,*) __COMPILER__
end program testit

The Fortran Wiki shows commands for several compilers that dump a list
of the pre-defined macros. Pre-processing is generally made much more
powerful by predefined macros but it is very easy to miss how to display
them and there are no standard ones, so each compiler has different ones.

The most common use in the past that is now generally replaced by using
modules was to define COMMON blocks in #include files. COMMON blocks are
very prone to getting out of sync when maintained separately at each point
they are used. Putting the definitions in an #include file or defining them
as decks in UPDATE allowed you to keep just one definition of the COMMON.
Without that ā€œtrickā€ a LOT of bugs were caused by COMMON definitions changing
in one reference but not in another.

There are so many subtle differences between the various cpp and fpp
commands out there that I made my own a long time ago; so I am a bit
rusty with cpp. It is not needed nearly as much as in the past to isolate
platform-specific code, which is a good thing. And upcoming Fortran changes
to support templating will hopefully reduce that more; but just about the
time you think pre-processing is not needed a change comes along that
ends up requiring it.

There is a standalone single-file version of prep(1) in the standalone/
directory of the github repository where the pre-processor I use is at
for alternative ideas about preprocessing for those not brave enough to
use m4(1) ā€¦

Maybe slightly off-topic, but I my opinion, we should avoid preprocessor magic whenever possible. (And I say it despite of (or maybe because of) being the main author of fypp :laughing:) It obfuscates code more and makes it also for IDEs more difficult to give meaningful support during development (especially, if it involves joining of strings ab above).

The _setopt_ macro could be easily realized with a simple function:

pure function default_optional(def, opt) result(val)
  integer, intent(in) :: def
  integer, intent(in), optional :: opt
  integer :: val

  if (present(opt)) then
    val = opt
  else
    val = def
  end if

end function default_optional
[...]
argval = default_optional(42, argval_)

Agreedly, it is painful to define it for each data type you need separately (we use the loop construct in fypp to generate it), but Fortran 202Y generic feature should alleviate that and we wonā€™t need a pre-processor for that any more.

I donā€™t really know if this is true, but I have heard that the first versions of the c++ language were implemented as cpp macros.

I agree. Nonetheless, these use cases also illustrate some part of the language that could be better.

In Stroustrupā€™s book The C++ Programming Language (3rd edition), with regards to preprocessing he writes: ā€œā€¦ The first rule about macros is: Donā€™t use them unless you have to. Almost every macro demonstrates a flaw in the programming language, in the program, or in the programmer.ā€

He later writes: Using macros, you can design your own private language. Even if you prefer this ā€œenhanced languageā€ to plain C++, it will be incomprehensible to most C++ programmersā€¦ The const, inline, template, enum, and namespace mechanisms are intended as alternatives to many traditional uses of preprocessor constructsā€¦

Much of my use of preprocessing these days is simply replicating code for various type/kind/rank combinations. It is PITA to do it with a cpp-like preprocessor. The fypp preprocessor is much better. But even then, the disadvantage is that you can easily end up with an exponential number of variations of the code - almost all of which are never used. It is why some sort of built-in templating or generic capability which only generates the versions of code actually used is needed.

2 Likes

Iā€™ve wondered if a safer version of statement functions could be used in the place of some of the preprocessor tricks people use. I know that internal procedures were designed to replace them and in general agree that they are to be preferred over statement functions but still I see value in being able to do something like:

Subroutine aval
!! Type definitions
macro
   a(i,j) = this%amat(i+(j-1)*this%imax)
   b(i,j) = this%bmat(i+(j-1)*this%imax)
end macro

!! executable body of aval
do j=1,this%jmax
   do i= 1, this%imax
     ab = a(i,j) * b((i,j)
!! some stuff that uses ab
  end do
enddo

I personally would prefer this to trying to use ASSOCIATE which I find in most cases very unweildy to use. The rules on things in a macro block would be.

  1. All arguments are considered intent(in)
  2. Like statement functions they must be defined before all other executable statements.
  3. The implied type of the result is taken from the types of the variables on the RHS with floating point taking precedent over integers in mixed mode arithmetic or like block statements allow the type to be defined after the macro statement

Again, I agree that internal routines are probably a better option but for simple things like remapping indicies in rank 1 arrays etc I think they can be overkill

IMO, the specific case of remapping indexes can be done quite elegantly in Fortran using pointer array remapping and internal procedures.

module somemod
implicit none
public

type :: sometype
    integer :: imax, jmax
    real, allocatable :: amat(:), bmat(:)
end type

contains

    subroutine aval(this,res)
        type(sometype), intent(in), target :: this
        real, intent(out) :: res

        real, pointer, contiguous :: a(:,:), b(:,:)
        real, allocatable :: c(:,:)

        associate(imax => this%imax, jmax => this%jmax)

            ! Create 2-d views
            a(1:imax,1:jmax) => this%amat
            b(1:imax,1:jmax) => this%bmat
    
            ! Result array
            allocate(c(imax,jmax))
    
            ! Numerical operations
            call body(imax,jmax,a,b,c)

        end associate

        ! Bogus operation so the body doesn't get optimized away
        res = maxval(c)

    contains

        ! Use subroutine to imply no aliasing between arguments
        subroutine body(imax,jmax,a,b,c)
            integer, intent(in) :: imax, jmax
            real, intent(in) :: a(imax,jmax), b(imax,jmax)
            real, intent(out) :: c(imax,jmax)
            integer :: i, j
            ! Some loopy code with 2-d indexing
            do j = 1, jmax
                do i = 1, imax
                    c(i,j) = a(i,j) * b(i,j)
                end do
            end do
        end subroutine

    end subroutine

end module

Itā€™s a bit verbose, but hopefully this aids clarity in the long-run, for both future readers and compilers alike. Matt Godbolt (the creator of Compiler Explorer) made the following appeal,

[ā€¦] Donā€™t compromise readability. [ā€¦] Trust your compiler to take readable, clear code that you can reason about. Turns out if you can reason about it, the compiler can reason about it and it can do the right thing.

This is of course a trivial example, and the compiler easily generates SIMD instructions.

On the other hand in C, OpenCL and even C++ codes it is still common to use the preprocessor for calculating linear indexes. But it quickly becomes tedious when d >= 3.

Yes, pointer remapping can be elegant but they are still pointers and come with the baggage that plague pointers (even relatively ā€œsafeā€ ones like Fortran pointers). One of the standard programming practices you would see Way Back When was to store everything in a large rank one array (an example might be the conservation variables along with other variables in a CFD calculation) and then provide starting indicies for each variable in the array. For 2D and 3D calculations the rank remaping in my example (using statement functions) was also standard when you needed to sweep along one coordinate direction as the inner loop. Frankly, one of the biggest problems with statement functions was readability because a lot of programmers for some reason never put in comment cards to alert users that the following line or lines were statement functions. They just assumed folks would figure that out by the placement of the statements before the first executable statement. Iā€™m not opposed to pointers for the things like lists where they are somewhat mandatory (although Fortran does allow recursive allocatable types). I just prefer a non-pointer solution if there is one that works equally well. In the end its a matter of personal preference and I prefer to limit pointer usage in my codes to just the things that are harder to do without pointers.

Back in the days of limited memory, a pointer might be 16 bits, 24 bits, or 32 bits, while the floating point object it addressed was 64 bits. In this situation, there were also practical advantages to using pointers for shallow assignment and shallow copy types of operations.

These days, the situation is reversed, with 64-bit memory addresses pointing at 16-, 32-, and 64-bit data. And, of course, fortran pointers contain more than just the raw memory address, which makes the imbalance even worse.

1 Like

Note that in your example you could directly pass the amat and bmat arrays to the body() routine, as the dummy arguments have explicit shapes. Which was generally the right way to do that when one had a large rank 1 array.

1 Like

Good point. We could replace the body with c = a * b, to make use of the newly acquired array shape.

I also like statement functions for simplifying indexing expressions. The compilers seem to inline them automatically. I donā€™t know why theyā€™ve been marked as obsolescent. They would be useful for this StackOverflow answer: What is the correct way of computing $LL^T$ in packed format with blas/lapack - Computational Science Stack Exchange.

Maybe we can bring them back in the form of something that approximates C++ lambdas. My first impression of lambdas is they shared some of the functionality of statement functions. As I tried to point out above they also can be used in some cases in the place of cpp logic and as you point out have the advantage of offering a greater possiblility of inlining. The biggest advantages I see of lambdas is they can be defined anywhere in the code and like block constructs can contain explicit typing. So maybe a lambda block construct would give us the advantages of statement functions without what I see is their biggest problem which is a potential for confusion with arrays and in general readability.

I donā€™t think there is any practical difference with respect to inlining between a statement function and a contained procedure. The main differences are that the contained procedure is a little more verbose and more flexible (e.g. both subroutines and functions are allowed, along with local variables, argument intent, and so on). If a contained procedure is not inlined when you think it should be, try adding the pure attribute to see if that helps.

The only practical problem Iā€™ve had when replacing statement functions with contained procedures is that you sometimes exceed the contained procedure nesting level. A module procedure is allowed only one level of nesting. When that happens, you must either rearrange the code to promote the procedure up one level, or you keep the statement function. That promotion option probably does eliminate the possibility of inlining since it is no longer contained within its calling procedure. It has been suggested here in previous discussions to eliminate the contained procedure nesting limit in the standard in order to facilitate modernization of legacy codes.

It seems that itā€™s always kind of a love-hate relationship between Fortran and preprocessing.

Now considering that Fortran does not support generics (yet), macros can be quite useful to fix some of the flaws of the language. There are several libraires available to provide generic containers:

Personally, I find preprocessing quite fun. You can experiment various things and bring new functionalities to the language. I collected the different experimentations I did over the years: fortiche.

The repo contains several test:

Folder Description
app Introduces the console keywords for build command line applications. It contains a simple argument parser and provides a fine control on the exit sequence. It also introduces the macros _COMPILER_NAME and _OS_NAME
array Introduces the keywords reallocate, reallocate_with, reallocate_as and resize for allocatable arrays.
assertion ā€˜assertionā€™ is a single-file, dependency-free, and simple micro framework for unit testing in fortran. The API is modeled after googletest
contract Introduces the concept of multiple inheritance into fortran. In addition, one can define a contract (abstract types without components) only containing clause (i.e. defered procedures)
export Exports functions using DEC extension
logging Introduces info, warn, debug, error and fatal. This exemple is a very simple logging library. The logging level is controlled with the environment variable LOGGING_LEVEL
logical Introduces short-circuiting logic to the language. In other words, in the block if cond1() .and. cond2() then, cond2() is not evaluated when cond1() returns false
loop Introduces the foreach construct together with only() and exclude() filters
namelist Introduces serialize and deserialize generic functions for derived type that can be written to namelists
optional Introduces optionalize to deal with optional parameters and reduce slightly the verbosity

have fun!

4 Likes

For sure. There is a very long history of preprocessors in the Fortran world.

Back in the 1970s, there was a survey of ā€œStructured Fortranā€ preprocessors by Loren Meissner. He documented over fifty in use! The need for them dwindled when Fortran 77 and Fortran 90 introduced ā€œbuilt inā€ structured programming constructs and other features (e.g., free form source, user-defined data types, etc.)

A lot were called ratfor. I know some ratfor preprocessors were in use long after the standards were modernized partly because they worked with a lot of compilers that did not have the new features yet. There were claims by some they produced faster code but I do not know if that was generally true. Put the ā€œrational FORTRANā€ preprocessors were in wide use at one time, and allowed even FORTRAN66 to be used with if/else/endif and do/enddo and so on long before most compilers supported them.

Ratfor - Wikipedia

Several were written in FORTRAN. I know at least one was written in Fortran90.

This article by Meissner in 1975 mentions twenty. One of which is ratfor: https://dl.acm.org/doi/pdf/10.1145/987316.987320

By august of 1975, he was up to 51. (List published in Meissnerā€™s For-Word newsletter.) Still only one version of ratfor.