Preprocessor conditional datatype best practice

Hello. Sorry if this question has been asked before, I tried searching around and couldn’t find it.

As the title suggests, I am wondering about the best practice for conditionally defining datatypes known at compile time. In my case, I have some code that can be executed identically for real or complex input data. Most of the time the input will just be real data, but I want to add complex input functionality. The code does the same operations whether or not the input data is real or complex, but for performance reasons I would like real to only be handled as real and only define complex as needed. Before the code is run, the input is known to be real or complex, so my thought is to just have a compiler flag that says whether or not to compile using real or complex in the following fashion:

program dtype_test
    implicit none
    
#ifdef CPLX
#define DTYPE COMPLEX
#else
#define DTYPE REAL
#endif

    DTYPE :: x
    x = (2.5, 3.1)
    print *, x
        
endprogram dtype_test

Which compiles and runs as expected for me entering ifx dtype_test.f90 -fpp (though the Modern Fortran vscode linter complains).

Alternatively I could have had #ifdef statements for each variable I declare, but that would result in roughly twice as many lines of code (one for complex, one for real declarations) when I could just write DTYPE as appropriate.

Anyways, I just wanted to know if there is a generally accepted ‘better’ approach to this type of conditional compilation, or if there is some other better approach that I haven’t thought of.

If this is the case, I think that the approach you proposed is the best way to go. However, since you want to add complex input functionality, I would suggest creating routines for real and complex types separately in a module and then use them in the main program:

module defs
  implicit none
  private
  public :: work
  interface work
    module procedure :: work_r
    module procedure :: work_c
  end interface work
contains
  subroutine work_r(x)
    real, intent(out) :: x
    x = (2.5, 3.1)
  end subroutine
  subroutine work_c(x)
    complex, intent(out) :: x
    x = (2.5, 3.1)
  end subroutine
end module defs

program main
  use defs, only: work
  implicit none
  real :: x
  complex :: y
  call work(x)
  call work(y)
  print*, x
  print*, y
end program main

To generate this module from the program that you already have, I would suggest you take a look at Fypp, a thread was opened here recently.

2 Likes