Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations SkipVought on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

Passing a variable amount of functions as an argument

Status
Not open for further replies.

GerritGroot

Technical User
Nov 3, 2006
291
0
0
ES
Hi,

In this forum I once saw a way to pass a function as an argument to another function or subroutine:

Would it be possible to pass a function as an argument wherein the amount of functions that you pass as an argument is variable?

Thanks,

Gerrit
 
I don't understand clearly the question. If you want to pass an array of functions or procedures, this is possible since F2003. For instance (simpler solutions are possible too) :

Code:
MODULE proc_mod

  IMPLICIT NONE
  
  ABSTRACT INTERFACE
    REAL FUNCTION f(x)
      REAL :: x
    END FUNCTION 
  END INTERFACE
  
  TYPE my_type
    PROCEDURE(f),NOPASS,POINTER :: proc
  END TYPE
  
  CONTAINS
  
  REAL FUNCTION f1(x)
    REAL :: x
    f1=x+1
  END FUNCTION 
  REAL FUNCTION f2(x)
    REAL :: x
    f2=x+2
  END FUNCTION 
  SUBROUTINE my_sub(listfunc)
    TYPE(my_type) :: listfunc(:)
    INTEGER :: i
    DO i=1,SIZE(listfunc)
      WRITE(*,*) listfunc(i)%proc(0.)
    ENDDO
  END SUBROUTINE
END MODULE

PROGRAM main
  USE proc_mod
  TYPE(my_type) :: listfunc(2)
  listfunc(1)%proc => f2 
  listfunc(2)%proc => f1  
  CALL my_sub(listfunc)
END PROGRAM

With the result :

lcoul@balade:~/test$ ifort t50.f90
lcoul@balade:~/test$ ./a.out
2.000000
1.000000
lcoul@balade:~/test$


François Jacq
 
Which version of Fortran are you using? With the earlier versions you may have to fiddle about with Cray pointers.
 
Hi,

Sorry for reacting so late, I was on a trip. Thanks for the example code, I am using gfortran, no idea if F2003 is included in there.

Your code may look simple, but for someone who never programmed with pointers it's a big step. Anyway your solution is more complicated than I hoped.

I'll have to study some fortran2003 school books before being able to adapt your example to my needs. This may take more time than, at least for the time being, program some special case.

I hope to get back to this,

Gerrit
 
Hi GerritGroot,
I tried the code posted by FJacq.

It doesn't compile for example with version:
GNU Fortran (GCC) 4.4.0 20080603,

but it compiles and runss fine for example with compiler versions:
GNU Fortran (GCC) 4.8.0 20121210 and G95 (GCC 4.0.4 (g95 0.92!) Oct 14 2008)
 
A slightly shorter solution with iso_c_binding (F2008)

Code:
MODULE proc_mod

  USE, intrinsic :: iso_c_binding

  IMPLICIT NONE
  
  CONTAINS
  
  FUNCTION f1(x) BIND(C) RESULT(r)
    REAL(C_FLOAT) :: x,r
    r=x+1
  END FUNCTION 
  
  FUNCTION f2(x) BIND(C) RESULT(r)
    REAL(C_FLOAT) :: x,r
    r=x+2
  END FUNCTION 
  
  SUBROUTINE my_sub(listfunc)
    TYPE(c_funptr) :: listfunc(:)
    PROCEDURE(f1),POINTER :: f
    INTEGER :: i
    DO i=1,SIZE(listfunc)
      CALL c_f_procpointer(listfunc(i),f)
      WRITE(*,*) f(0.)
    ENDDO
  END SUBROUTINE
  
END MODULE

PROGRAM main
  USE proc_mod
  TYPE(c_funptr) :: listfunc(2)
  listfunc(1)=c_funloc(f2) 
  listfunc(2)=c_funloc(f1) 
  CALL my_sub(listfunc)
END PROGRAM

François Jacq
 
Also works on gfortran 4.6.1.

If you type gfortran --version, it will tell you which version you are using.
 
Here is another variant: generic interfaces. The only drawback is that the parameters in the subroutines must be different. You can do this with F95 compilers.
Code:
module mod_generic
contains
   subroutine funky1(ii)
      integer ii, res
      res = ii
      print *, 'funky1 = ', res
   end subroutine funky1

   subroutine funky2(ii, jj)
      integer ii, jj, res
      res = ii * jj
      print *, 'funky2 = ', res
   end subroutine funky2

   subroutine funky3(ii, jj, kk)
      integer ii, jj, kk, res
      res = ii * jj * kk
      print *, 'funky3 = ', res
   end subroutine funky3
end module mod_generic

program main
   use mod_generic
   interface funky
      module procedure funky1, funky2, funky3
   end interface funky

   call funky(1)
   call funky(1, 2)
   call funky(1, 2, 3)
end program main
funky1 = 1
funky2 = 2
funky3 = 6


 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top