Selection of correct procedure/function at runtime (F2008)

Hello!

TL;DR

What is the correct way to select the correct procedures for different computational models at runtime?

Introduction

I am creating a code that will require the computation of different fluid properties. However, the code needs to support different fluid models (ideal, perfect, table, real, etc). The fluid model to be used will not be know at compile time.

Goal

It would be ideal if the rest of the application does not know about the underlying models. For example:

! Ideal scenario
enthalpy = enthalpy_from_PT(P, T)

! Not ideal
enthalpy = enthaypy_from_PT(fluid_type, P, T)

Ideally, at the beginning of the program, the generic function would be set up to “point” (one can tell I come from a C background) to the requested implementation by the user. How would this be achieved?

Issue

One of the reasons I am asking is because I know modern Fortran (in my case it is Fortran 2008) has a lot of tricks up its sleeve, and this is probably simple to do. I know that in F2003 the select type construct exists, but it is only for objects.

I thought about making a different object for every fluid model with intrinsic functions that are then selected by select type but that would leave the code as:

enthalpy = fluid_obj%HfPT(P, T)

which seem a bit messy: having a fluid type with no data and only procedures, and calling an object method to do a normal function call.

Any help (or pointers to blogs, papers, other code, etc) is greatly appreciated.

Regards,

Fernando

2 Likes

I would use an abstract base class to define the interfaces for each of the procedures needed for fluid type. Then you can implement a different type that extends from that for each of the desired types. The code that uses them has a variable of class(base_type), whether input or allocated, and doesn’t need to know anything about the different implementations. No select type constructs or model type arguments needed. This is pretty much exactly the problem polymorphism was intended to solve.

1 Like

Fernando,

I’ll suggest you review a few books on modern Fortran as mentioned in this Dr Fortran blog: Doctor Fortran in "It's a Modern Fortran World" - Doctor Fortran

and especially take a close look at, “Scientific Software Design: The Object-Oriented Way”. Even though this book is based more on Fortran 2003, it will allow you to think further on code design aspects and patterns, etc. This book is especially strong on object-oriented design and what you can achieve with polymorphism, information hiding, data encapsulation, etc.

As to your question in the original post here, it’s unclear yet what you seek: your explanation suggests overloading methods to a generic interface is perhaps adequate? See a trivial example below. May be you can explain more what you have tried and what further you wish to have and readers may be able to provide input.

module ideal_gas_m
! Say you have a module for the ideal gas approach to physical properties
   real, parameter :: h0 = 0.0 ! Arbitrary reference enthalpy
   real, parameter :: R = 8.314472 ! Universal gas constant, J/mol*K
contains
   function ideal_gas_enthalpy(T) result(h)
      real, intent(in) :: T
      ! Function result
      real :: h
      print *, "Using ideal_gas_enthalpy procedure .. "
      h = h0 + 3.5*R*T ! some suitable relationship
   end function
end module
module real_gas_m
! Say you have a module for the real gas model for physical properties
   real, parameter :: href = 0.0 ! Arbitrary reference enthalpy
   real, parameter :: A_1 = 10.0
   real, parameter :: B_1 = 20.0
   real, parameter :: A_2 = 100.0
   real, parameter :: B_2 = 200.
contains
   function real_gas_enthalpy(fluid_type, P, T) result(h)
      type(integer), intent(in) :: fluid_type ! suitable type; shown here as integer
      real, intent(in) :: P
      real, intent(in) :: T
      ! Function result
      real :: h
      print *, "Using real_gas_enthalpy procedure .. "
      h = 0.0
      if (P < 0.0) then
         ! suitable action
      end if
      select case ( fluid_type )
         case ( 1 )
            h = href + A_1 + B_1*T
         case ( 2 )
            h = href + A_2 + B_2*T
         case default
            ! error handling?
      end select
   end function
end module
   use ideal_gas_m
   use real_gas_m
   interface enthalpy_from_PT
   ! Your program can combine the interfaces to a generic one
      procedure ideal_gas_enthalpy
      procedure real_gas_enthalpy
   end interface
   integer :: model
   real :: P, T, h
   print *, "Enter enthalpy model: 0 for ideal gas, 1 for real gas"
   read *, model
   P = 1E5 ; T = 300.0 ! Pa. K for P, T state conditions
   select case ( model )
      case ( 0 )
         h = enthalpy_from_PT( T )
      case ( 1 )
         h = enthalpy_from_PT( 1, P, T )
   end select
   print *, "h = ", h, " J/mol"
end

Here’s the program response:

C:\Temp>gfortran -Wall p.f90 -o p.exe

C:\Temp>p.exe
Enter enthalpy model: 0 for ideal gas, 1 for real gas
1
Using real_gas_enthalpy procedure …
h = 6010.00000 J/mol

C:\Temp>p.exe
Enter enthalpy model: 0 for ideal gas, 1 for real gas
0
Using ideal_gas_enthalpy procedure …
h = 8730.19629 J/mol

C:\Temp>

1 Like

Welcome to the Discourse @Irvise!
There hasn’t yet been any mention of procedure pointers which would seem like a valid solution to this problem.

This would assume the interface is the same across implementations (unlike the generics case).
There’s a simple example of procedure pointers here.

For your case, perhaps something roughly along the lines of:

...
interface
  function enthalpy_from_PT(P, T) result (h)
    real, intent(in) :: P, T
    real :: h
  end function enthalpy_from_PT
end interface

procedure(enthalpy_from_PT), pointer :: enthalpy => NULL()

select case ( fluidModel )
  case ( IDEALGAS )
    enthalpy => enthalpy_from_PT_ideal
  case ( REALGAS )
    enthalpy => enthalpy_from_PT_real
end select

h = enthalpy(P,T)
...

where enthalpy_from_PT_ideal and enthalpy_from_PT_real are functions conforming to the enthalpy_from_PT interface.

Note that the procedure pointer assignment does not need to occur within the main program, i.e. the main program does not need to be aware of all possible fluid models, only of the procedure interface(s).

1 Like

@everythingfunctional
Thank you for your suggestion. I will take a look at abstract classes and interfaces. I knew they existed but I never learnt them properly. Btw, congrats on getting your talk accepted :slight_smile:

@FortranFan
Thank you for the resources! I indeed need to get some form of library to back me up. Your code example show in a more precise way what I would like to evade. I would prefer not to use a select case statement in the project every time I want to compute some fluid property. This method would make the “main” flow of the program too verbose.

@lkedward
Thank you very much for your suggestion. This is exactly what I wanted! I did not know that Fortran allowed procedure pointers, that is pretty sweet (and it resembles C a bit).

Hopefully I will be able to make this work with submodules so that the entire fluid system becomes quite neat.

2 Likes

@lkedward wrote June 18, 2020 4:15 AM EDT:

There hasn’t yet been any mention of procedure pointers which would seem like a valid solution to this problem.

@lkedward, do note @Irvise’s original post clearly showed different signatures (interfaces) to the 2 enthalpy functions (enthalpy_from_PT(P, T) vs enthaypy_from_PT(fluid_type, P, T)) and as such, the procedure pointer solution didn’t apply.

Besides the procedure pointer solution is generally a stopover on the way toward a more comprehensive object-based or object-oriented design in one’s codebase. Learning/reviewing OO design techniques in a more structured manner from book(s) is what will benefit someone like OP, based on the original post.

I don’t think that’s a real obstacle. The ideal scenario of enthalpy_from_PT(P, T) could be easily reworked to accept an (ideal) fluid_type instance as argument, so that the interfaces are consistent.

I also prefer the procedure pointer approach for a problem like this. More importantly, @Irvise can now choose between few different approaches to pick their favorite.

2 Likes

A poster about procedure pointers:

@Irvise beyond the excellent suggestions that you have already received, I would add that it is typical for this sort of applications (for a number of reasons, including efficiency) to encapsulate in the derived type the state of the fluid (where you collect the name of the fluid, its model, its phase, etc…). A low-level interface sets this although the high-level interface lets the user select simply the variables of interest (e.g. pressure and temperature, like in your example) and will compute the state of the fluid behind the scenes in the most efficient way.

Depending on the type of library or application you are aiming at, this additional complexity might be over-engineering or essential. I’m pointing this out because it, obviously, affects the signature of your procedures and the different ways that you want to go about it using the above strategies.