Calling different functions with an integer

Hey everyone,

I am trying to call different functions according to the integer that I have.
Here is the python code that I am trying to convert into fortran :

def fct1(x):
   return x

def fct2(x):
   return x**2

def fct3(x):
   return x**3

fct_choice=[fct1, fct2, fct3]

print(fct_choice[0](5))

So far I can only imagine using IF or SELECT CASE statements, but I would like to avoid using them. I imagine one can do this using procedures, … but I’m not familiar enough with fortran to know how to do that. Would anyone have an idea on how to convert this python code into fortran?

Thank you for your answers!

You could emulate that using a Fortran array of function pointers.

Something along the lines of:

program test
   implicit none
   type :: fct_t
      procedure(procInterface), nopass, pointer :: fct_ => null()
   end type
   abstract interface
      integer function procInterface(val) result(res)
         integer, intent(in) :: val
      end function
   end interface

   type(fct_t) :: func_ptrs(4)
   integer :: i_choice = 4

   call setFunctions()
   print *, eval(i_choice, 0)

contains

   subroutine setFunctions()
      func_ptrs(1)%fct_ => f1
      func_ptrs(2)%fct_ => f2
      func_ptrs(3)%fct_ => f3
      func_ptrs(4)%fct_ => f4
   end subroutine

   integer function eval(ichoice, val) result(res)
      integer, intent(in) :: ichoice, val

      res = func_ptrs(ichoice)%fct_(val)
   end function


   integer function f1(val) result(res)
      integer, intent(in) :: val

      res = val + 1
   end function

   integer function f2(val) result(res)
      integer, intent(in) :: val

      res = val + 2
   end function

   integer function f3(val) result(res)
      integer, intent(in) :: val

      res = val + 3
   end function

   integer function f4(val) result(res)
      integer, intent(in) :: val

      res = val + 4
   end function
end program

Ideally, in such case, you might want only expose the eval function and keep everything else hidden from the user, except if you know who and how’s the code used.

Better still (in my opinion, at least): make eval a “method” of the fct_t derived type (in Fortran terms: a type-bound procedure). Then:

print *, i_choice%eval(i_choice, 0)

to invoke the right function.

I leave the other change you need as an exercise :slight_smile:

2 Likes

And continuing with your suggestion, with the right tweaks, even completely avoid passing the choice in the eval function (which I don’t particularly like), so to have:

print *, i_choice%eval(0)

which I find more elegant in an API view point.

2x :slight_smile: