Skip to content

Precision-agnostic Fortran interface

I would like to discuss several approaches to how we can implement add_var in the Fortran interface.

We want the type safety. Therefore, one way or another, we need to call add_var_float32, add_var_float64, add_var_int16, etc., depending on the type of the variable the user wants to have. I intend to expose those functions via the Fortran interface so the users can have better control if they want or need it. However, we also need to support a way for the users to write precision-agnostic code. And I don't have a perfect solution for this.

Say, the user code looks like

MODULE mo_kind
  ! In real code, the values below are evaluated at the compilation time
  ! and can be anything, depending on the compiler in use (i.e. the
  ! Fortran standard does not enforce anything regarding this). Also
  ! note that the kind constants have no meaning on their own but only
  ! in combination with the type: REAL, INTEGER, etc.
  INTEGER, PARAMETER :: sp = 1 !single precision kind for REAL variables
  INTEGER, PARAMETER :: dp = 2 !double precision kind for REAL variables
  INTEGER, PARAMETER :: i1 = 1 !INTEGER kind that supports values (at least) in range [-128; 127] (one byte)
  INTEGER, PARAMETER :: i2 = 2 !INTEGER kind that supports values (at least) in range [-32,768; 32,767] (two bytes)
#ifdef __MIXED_PRECISION
  INTEGER, PARAMETER :: wp = sp
#else
  INTEGER, PARAMETER :: wp = dp
#endif
END MODULE mo_kind

MODULE some_component
  USE mo_kind, ONLY: wp
  USE memman, ONLY: !TBD
CONTAINS
  SUBROUTINE subroutine init()
    ! the user wants to add a variable of type REAL(KIND=wp) here
  END SUBROUTINE init
END MODULE some_component

As you can see in the code above, the user wants to work with a variable of type/size that she does not know at the time of writing the code. It will be known at the compilation time only (depending on whether the __MIXED_PRECISION macro is defined). How do we support that? I have several solutions in mind:

  1. Implement add_var_real and add_var_integer as follows:
    MODULE memman
    CONTAINS
      FUNCTION add_var_real(..., kind) result(err_code)
        INTEGER, INTENT(IN) :: kind
        INTEGER :: err_code
    
        SELECT CASE(kind)
          CASE (c_float)
            err_code = add_var_float32(...)
          CASE (c_double)
            err_code = add_var_float64(...)
          CASE DEFAULT
            err_code = -1
        END SELECT
      END FUNCTION add_var_real
      ! the same for INTEGER
    END MODULE memman
    and the user code would look like
    MODULE some_component
      USE mo_kind, ONLY: wp
      USE memman, ONLY: add_var_real
    CONTAINS
      SUBROUTINE subroutine init()
        add_var_real(..., wp)
      END SUBROUTINE init
    END MODULE some_component
  2. Delegate it to the user (no extra code in memman):
    1. Quick and dirty:
      MODULE some_component
        USE mo_kind, ONLY: wp
        USE memman, ONLY: add_var_float32, add_var_float64
      CONTAINS
        SUBROUTINE subroutine init()
      #ifdef __MIXED_PRECISION
          add_var_float32(...)
      #else
          add_var_float64(...)
      #endif
        END SUBROUTINE init
      END MODULE some_component
    2. Via an intermediate module:
      MODULE my_memman
        USE memman, ONLY: add_var_float32, add_var_float64, &
      #ifdef __MIXED_PRECISION
                        & add_var_real => add_var_float32
      #else
                        & add_var_real => add_var_float64
      #endif
      END MODULE my_memman
      
      MODULE some_component
        USE mo_kind, ONLY: wp
        USE my_memman, ONLY: add_var_real
      CONTAINS
        SUBROUTINE subroutine init()
          add_var_real(...)
        END SUBROUTINE init
      END MODULE some_component
  3. Same as 2. but in memman, i.e. the user has to recompile the library together with the code to get another precision.
  4. Declare a polymorphic interface add_var:
    MODULE memman
      INTERFACE add_var
        MODULE PROCEDURE add_var_sp
        MODULE PROCEDURE add_var_dp
        ! we can cover INTERGER here too
      END INTERFACE add_var
    CONTAINS
      FUNCTION add_var_sp(..., dummy) result(err_code)
        REAL(c_float), INTENT(IN) :: dummy
        CALL add_var_float32(...)
      END FUNCTION add_var_sp
    
      FUNCTION add_var_dp(..., dummy) result(err_code)
        REAL(c_double), INTENT(IN) :: dummy
        CALL add_var_float64(...)
      END FUNCTION add_var_dp
    END MODULE memman
    and the user code would look like
    MODULE some_component
      USE mo_kind, ONLY: wp
      USE memman, ONLY: add_var
    CONTAINS
      SUBROUTINE subroutine init()
        REAL(wp), POINTER :: dummy ! POINTER to prevent allocation
        add_var(..., dummy)
      END SUBROUTINE init
    END MODULE some_component

I'm pretty sceptical of the idea to rebuild/reinstall memman together with the user code. We are working on a library, which, once installed, should just work. Therefore, I don't seriously consider 3. At least for now. Option 2.2 is fine, I guess, but requires an extra layer on the user side, i.e. memman cannot be used as is, which was the original idea. Option 4 would be great, especially if we take into account that we also need size/shape of the variables but passing a dummy argument looks very counter-intuitive to me, i.e. the user has to make sure that the variable she passes to add_var is not automatically allocated and the function does not really do anything to the argument. I also don't know how we can get rid of the compiler warnings about the unused dummy variables. So, I plan to go for 1 for now as the most simple and straightforward approach. The performance penalty of select case and an extra jump does not seem to be significant.

Edited by Sergey Kosukhin
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information